RecursionLock.st
author Claus Gittinger <cg@exept.de>
Tue, 09 Jul 2019 20:55:17 +0200
changeset 24417 03b083548da2
parent 24352 9937850c76ee
child 24903 5994d90bff22
permissions -rw-r--r--
#REFACTORING by exept class: Smalltalk class changed: #recursiveInstallAutoloadedClassesFrom:rememberIn:maxLevels:noAutoload:packageTop:showSplashInLevels: Transcript showCR:(... bindWith:...) -> Transcript showCR:... with:...

"
 COPYRIGHT (c) 1995 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libbasic' }"

"{ NameSpace: Smalltalk }"

Semaphore subclass:#RecursionLock
	instanceVariableNames:'process'
	classVariableNames:''
	poolDictionaries:''
	category:'Kernel-Processes'
!

!RecursionLock class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1995 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

!

documentation
"
    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
    is the one which did the original locking.

    WARNING:
	for now, recursionLocks are not unlocked when an image is
	restarted. You may have to recreate them to avoid a deadLock.
	(this may change in the future, but recreating a recursionLock in
	 the #earlyRestart handling does not hurt)

    [author:]
	Claus Gittinger

    [see also:]
	Semaphore
	Process ProcessorScheduler
"
!

examples
"
  example (good):
									[exBegin]
    |lock|

    lock := RecursionLock new.
    lock critical:[
	Transcript showCR:'in lock ...'.
	lock critical:[
	    Transcript showCR:'again ...'
	]
    ]
									[exEnd]

  in contrast to (wrong example - deadlocks):
									[exBegin]
    |lock|

    lock := Semaphore forMutualExclusion.
    lock critical:[
	Transcript showCR:'in lock ...'.
	lock critical:[
	    '*** never reached - deadlock because sema is already locked ***'.
	    '    (press CTRL-c and abort in the debugger)'.
	    Transcript showCR:'again ...'
	]
    ]
									[exEnd]
"
! !

!RecursionLock class methodsFor:'instance creation'!

name:aString
    ^ self basicNew setCount:1 name:aString

    "Created: / 09-08-2017 / 11:47:21 / cg"
!

new
    ^ self basicNew setCount:1

    "Modified: / 20-02-2017 / 16:32:11 / stefan"
!

new:n
    ^ self shouldNotImplement

    "Created: / 20-02-2017 / 15:55:38 / stefan"
! !

!RecursionLock methodsFor:'blocked protocol'!

signalForAll
    ^ self shouldNotImplement

    "Created: / 20-02-2017 / 16:05:15 / stefan"
!

signalIf
    ^ self shouldNotImplement

    "Created: / 20-02-2017 / 16:05:19 / stefan"
!

signalOnce
    ^ self shouldNotImplement

    "Created: / 20-02-2017 / 16:05:25 / stefan"
!

waitUncounted
    ^ self shouldNotImplement

    "Created: / 20-02-2017 / 16:02:50 / stefan"
!

waitUncountedWithTimeoutMs:milliSeconds
    ^ self shouldNotImplement

    "Created: / 20-02-2017 / 16:04:31 / stefan"
! !

!RecursionLock methodsFor:'queries'!

owner
    "return the owning processes (or nil)"

    ^ process
!

wouldBlock
    "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|

    process ~~ Processor activeProcess ifTrue:[
	self error:'RecursionLock - signaling process doesn''t own the lock'.
    ].

    wasBlocked := OperatingSystem blockInterrupts.
    process := nil.
    super signal.
    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].

    "Modified: / 18-02-2017 / 21:44:40 / stefan"
! !

!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."

    |active retVal wasBlocked gotSema|

    active := Processor activeProcess.
    process == active ifTrue:[
        "I have already got the lock"
        ^ aBlock value
    ].

    "/
    "/ 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.
    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].
                    ].
    ].
    OperatingSystem blockInterrupts.
    process := nil.
    super signal.
    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
    ^ retVal.

    "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
     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
    ].

    "/
    "/ 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.
    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 state:#wait.
        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.
        super signal.
        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
    ] ifFalse:[
        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
        retVal := blockingBlock value.
    ].
    ^ retVal.

    "Modified (comment): / 22-02-2017 / 15:35:25 / stefan"
    "Modified: / 24-07-2017 / 21:17:29 / cg"
!

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.
    ].

    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.
    ].
    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 state:#wait.
    gotSema notNil ifTrue:[
        gotSema := true.
        process := active.
    ].
    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
    ^ gotSema.

    "Modified: / 24-07-2017 / 21:17:39 / cg"
! !

!RecursionLock class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !