RecursionLock.st
author Claus Gittinger <cg@exept.de>
Sat, 18 May 1996 17:32:43 +0200
changeset 1422 9a0b792f2953
parent 1316 248a8cb2ae3b
child 2143 09af9c997961
permissions -rw-r--r--
showCr: -> showCR:

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


Object subclass:#RecursionLock
	instanceVariableNames:'process sema'
	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 if the current process 
    is the one which did the original locking.


    [author:]
        Claus Gittinger

    [see also:]
        Semaphore
        Process ProcessorScheduler
"
!

examples
"
    example:
                                                                        [exBegin]
        |lock|

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

    in contrast to (wrong example):
                                                                        [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'!

new
    ^ self basicNew initialize

! !

!RecursionLock methodsFor:'private initialization'!

initialize
    sema := Semaphore forMutualExclusion
! !

!RecursionLock methodsFor:'queries'!

wouldBlock
    "return true, if the receiver would block the activeProcess
     if a wait was performed. False otherwise."

    process == Processor activeProcess ifTrue:[^ false].
    ^ sema wouldBlock

    "Created: 18.4.1996 / 17:18:08 / cg"
! !

!RecursionLock methodsFor:'wait & signal'!

critical:aBlock
    "evaluate aBlock as a critical region, but do not block,
     if this lock is already held by the current process."

    |active wasBlocked|

    active := Processor activeProcess.
    process == active ifTrue:[
        aBlock value
    ] ifFalse:[
        "/
        "/ 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.
        sema critical:[
            [
                process := active.
                wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
                aBlock value.
                OperatingSystem blockInterrupts.
            ] valueOnUnwindDo:[
                process := nil.
            ]
        ].
        process := nil.
        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
    ].

    "Modified: 13.4.1996 / 00:19:31 / stefan"
    "Modified: 18.4.1996 / 21:09:39 / cg"
! !

!RecursionLock class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/RecursionLock.st,v 1.14 1996-05-18 15:32:43 cg Exp $'
! !