RecursionLock.st
branchjv
changeset 23082 b75aec4476a4
parent 21249 86c01ee5a76e
child 23083 c8dcd89b9cf6
--- a/RecursionLock.st	Fri Aug 11 12:06:04 2017 +0100
+++ b/RecursionLock.st	Fri Aug 25 10:06:39 2017 +0100
@@ -14,7 +14,7 @@
 "{ NameSpace: Smalltalk }"
 
 Object subclass:#RecursionLock
-	instanceVariableNames:'process sema'
+	instanceVariableNames:'process sema count'
 	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:
@@ -96,7 +96,7 @@
 forMutualExclusion
     "same as new, for easy exchangability with regular mutual-exclusion Semaphores."
 
-    ^ self new 
+    ^ self new
 !
 
 new
@@ -145,13 +145,20 @@
 !RecursionLock methodsFor:'private-initialization'!
 
 initialize
-    sema := Semaphore forMutualExclusion name:'recursionLock'
+    sema := Semaphore forMutualExclusion name:'RecursionLock@' , self identityHash printString.
+    count := 0.
 
     "Modified: 25.1.1997 / 00:19:15 / cg"
 ! !
 
 !RecursionLock methodsFor:'queries'!
 
+count
+    ^ count
+
+    "Created: / 28-08-2017 / 21:53:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 numberOfWaitingProcesses
     "return the number of waiting processes"
 
@@ -167,183 +174,160 @@
 !
 
 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]]
 ! !
 
 !RecursionLock methodsFor:'signaling'!
 
-signal
-    |wasBlocked|
+release
+    "
+    Release the lock. Return true of lock has been released, `false` if
+    not (because calling process does not own it).
+    "
+    | active wasBlocked |
 
-    process ~~ Processor activeProcess ifTrue:[
-        self error:'RecursionLock - signaling process doesn''t own the lock'.
+    active := Processor activeProcess.
+    process == active ifFalse:[
+        "/ Oops,  calling thread does not own the monitor. return false
+        "/ immediately. The caller is responsible for throwing
+        "/ IllegalMonitorStateException...
+        ^ false.
     ].
+    wasBlocked := OperatingSystem blockInterrupts.
+    count == 1 ifTrue:[
+        process := nil.
+        count := 0.
+        sema signal.
+    ] ifFalse:[
+        count := count - 1.
+    ].
+    wasBlocked ifFalse:[ OperatingSystem unblockInterrupts ].
+    ^ true
 
-    wasBlocked := OperatingSystem blockInterrupts.
-    process := nil.
-    sema signal.
-    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+
+    "Created: / 25-08-2017 / 08:38:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+signal
+    self breakPoint: #jv.
+    self release ifFalse:[
+        self error: 'Attempt to release a (recursion) lock by process the does not own it!!'
+    ]
+
+    "Modified: / 25-08-2017 / 08:41:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !RecursionLock methodsFor:'waiting'!
 
-critical:aBlock
-    "evaluate aBlock as a critical region, but do not block
-     if this lock is already held by the current process."
+acquire
+    "
+    Acquire the lock:
+
+       * If the lock is not owned by any process, lock it and return immediately.
+       * If the lock is already owned by the calling process, return immediately.
+       * Otherwise, wait until owning process release it (by means of #release).
+
+    Return `true` (always)
+    "
+    ^self acquireWithTimeoutMs: nil
+
+
+    "Created: / 25-08-2017 / 08:34:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
 
-    |active retVal wasBlocked gotSema|
+acquireWithTimeoutMs: timeout
+    "
+    Acquire the lock:
 
+       * If the lock is not owned by any process, lock it and return immediately.
+       * If the lock is already owned by the calling process, return immediately.
+       * Otherwise, wait until owning process release it (by means of #release)
+         at most `timeout` milliseconds. If `timeout` is nil, wait forever.
+
+    Return `true` if the lock has been acquired or `false` if bot (e.g. wait
+    timed out)
+    "
+
+    | active wasBlocked acquired |
+    acquired := nil.
     active := Processor activeProcess.
     process == active ifTrue:[
-        "I have already got the lock"
-        ^ aBlock value
+        "/ Process already ackquired the monitor, increase the
+        "/ count and continue...
+        count := count + 1.
+        ^true.
     ].
-
-    "/
-    "/ sema wait & process := active
-    "/ and:
-    "/ proces := nil & sema signal
-    "/ must both be done atomic
-    "/ Scenario:
-    "/   ... recLock critical
-    "/         got lock
-    "/         evaluated
-    "/         set process to nil
-    "/         -> timer interrupt
-    "/              recLock critical in timeOut action
-    "/              process isNil
-    "/                 sema wait !!!!!! DEADLOCK
-    "/
     wasBlocked := OperatingSystem blockInterrupts.
     [
-        (process notNil and:[process isDead]) ifTrue:[
-            process := nil. 
-            'RecursionLock [warning]: cleanup lock from dead process' infoPrintCR.
-            sema signal.
+        (process notNil and:[ process isDead ]) ifTrue:[
+            "/ Process that acquired the monitor died without releasing it.
+            "/ This should not happen.
+            wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+            self assert: false description: 'Process that acquired the lock died without releasing it'.
+            process := nil.
+            count := 0.
         ].
-        gotSema := sema wait.
+        "/ We need to know that we already waited on and got semaphore
+        "/ in case the Semaphore >> #wait is prematurely terminated.
+        "/ Q: Can this actually happen? If so, how?
+        acquired := sema waitWithTimeoutMs: timeout.
         process := active.
+        count := 1.
         wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-        retVal := aBlock value.
     ] ifCurtailed:[
-        "be careful - the unwind may occur both while waiting
-         AND while evaluating the block"
-        gotSema notNil ifTrue:[
+        acquired notNil ifTrue:[
             OperatingSystem blockInterrupts.
+            count := 0.
             process := nil.
             sema signal.
         ].
         wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
     ].
-    OperatingSystem blockInterrupts.
-    process := nil.
-    sema signal.
-    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-    ^ retVal.
+    ^acquired notNil.
+
+    "Created: / 25-08-2017 / 22:55:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+critical:aBlock
+    "Evaluate aBlock as a critical region. Same process may
+     enter critical region again, i.e., nesting allowed."
+    ^self critical: aBlock timeoutMs: nil ifBlocking: nil
+
+    "Modified (comment): / 25-08-2017 / 09:47:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 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."
+    "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.
 !
 
 critical:aBlock timeoutMs:timeoutMs ifBlocking:blockingBlock
-    "like critical:, but do not block if the lock cannot be acquired 
-     within timeoutMs milliseconds.
-     Instead, return the value of blockingBlock."
-
-    |active retVal wasBlocked gotSema|
-
-    active := Processor activeProcess.
-    process == active ifTrue:[
-        "I have already got the lock"
-        ^ aBlock value
-    ].
+    "Like #critical:, but do not block if the lock cannot be acquired
+     within `timeoutMs` milliseconds. Instead, return the value of `blockingBlock.`"
 
-    "/
-    "/ sema wait & process := active
-    "/ and:
-    "/ proces := nil & sema signal
-    "/ must both be done atomic
-    "/ Scenario:
-    "/   ... recLock critical
-    "/         got lock
-    "/         evaluated
-    "/         set process to nil
-    "/         -> timer interrupt
-    "/              recLock critical in timeOut action
-    "/              process isNil
-    "/                 sema wait !!!!!! DEADLOCK
-    "/
-    wasBlocked := OperatingSystem blockInterrupts.
-    [
-        (process notNil and:[process isDead]) ifTrue:[
-            process := nil. 
-            'RecursionLock [warning]: cleanup lock from dead process' infoPrintCR.
-            sema signal.
-        ].
-        gotSema := sema waitWithTimeoutMs:timeoutMs.
-        gotSema notNil ifTrue:[
-            process := active.
-            wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-            retVal := 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].
-    ].
-    gotSema notNil ifTrue:[
-        OperatingSystem blockInterrupts.
-        process := nil.
-        sema signal.
-        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-    ] ifFalse:[
-        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-        retVal := blockingBlock value.
-    ].
-
-    ^ retVal.
+     | acquired |
+     acquired := self acquireWithTimeoutMs: timeoutMs.
+     acquired ifTrue:[
+     	^ aBlock ensure:[ self release ]
+     ] ifFalse:[
+     	^ blockingBlock value.
+     ].
 !
 
 wait
-    "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|
-
-    active := Processor activeProcess.
-    process == active ifTrue:[
-        "I have already got the lock"
-        ^ false.
-    ].
+    self breakPoint: #jv.
+    self acquire.
 
-    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. 
-        'RecursionLock [info]: cleanup leftover lock from dead process' infoPrintCR.
-        sema signal.
-    ].
-    sema wait.
-    process := active.
-    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-    ^ true.
+    "Modified: / 25-08-2017 / 08:40:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !RecursionLock class methodsFor:'documentation'!
@@ -354,5 +338,10 @@
 
 version_CVS
     ^ '$Header$'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !