RecursionLock.st
author Claus Gittinger <cg@exept.de>
Mon, 04 Dec 2000 16:13:27 +0100
changeset 5735 3c1f1f115640
parent 5104 99233ab3f6f5
child 6552 5ebab8a33da9
permissions -rw-r--r--
checkin from browser

"
 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:libbasic2' }"

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 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'!

forMutualExclusion
    "for easy exchangability with mutual-exclusion Semaphores..."

    ^ self new 
!

new
    ^ self basicNew initialize

! !

!RecursionLock methodsFor:'printing & storing'!

displayString
    "return a string to display the receiver - include the
     count and user-friendly name for your convenience"

    ^ self class name , '(' , sema count printString , ' name: ' , (self name ? 'unnamed') , ')'

    "Created: / 28.6.1997 / 16:20:33 / cg"
    "Modified: / 14.12.1999 / 21:04:08 / cg"
!

name
    "return the semaphores userFriendly name"

    ^ sema name

    "Created: / 28.6.1997 / 16:19:40 / cg"
    "Modified: / 14.12.1999 / 21:03:46 / cg"
!

name:aString
    "set the semaphores userFriendly name"

    sema name:aString

    "Created: / 28.6.1997 / 16:19:47 / cg"
    "Modified: / 14.12.1999 / 21:03:52 / cg"
! !

!RecursionLock methodsFor:'private initialization'!

initialize
    sema := Semaphore forMutualExclusion name:'recursionLock'

    "Modified: 25.1.1997 / 00:19:15 / cg"
! !

!RecursionLock methodsFor:'queries'!

numberOfWaitingProcesses
    "return the number of waiting processes"

    ^ sema numberOfWaitingProcesses

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

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 retVal wasBlocked|

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

    ^ retVal

    "Modified: / 5.3.1998 / 10:22:50 / stefan"
    "Modified: / 21.7.1998 / 17:44:06 / cg"
! !

!RecursionLock class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/RecursionLock.st,v 1.24 2000-12-04 15:13:27 cg Exp $'
! !