Monitor.st
author Claus Gittinger <cg@exept.de>
Fri, 11 Dec 1998 12:57:54 +0100
changeset 709 5a8ddf63e001
parent 699 01af80ac55c5
child 710 b17b877ac7b4
permissions -rw-r--r--
checkin from browser

"
 COPYRIGHT (c) 1996 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:#Monitor
	instanceVariableNames:'owningProcess sema count'
	classVariableNames:''
	poolDictionaries:''
	category:'Kernel-Processes'
!

!Monitor class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1996 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
"
    Monitors - functionality much like RecursionLocks, but not
    block based.
    Monitors are not unwind-save (i.e. a return or unwind while a
    monitor is locked, will lead to a deadlock situation).
    You have to care for unwinds yourself.

    Notice:
	This is an experimental demo class - there is no WARRANTY.
	Smalltalkers should use Semaphores and RecursionLocks, which
	are unwind-save.

    [see also:]
	RecursionLock Semaphore Delay SharedQueue
	Block

    [author:]
	Claus Gittinger
"

!

examples
"
						[exBegin]
	|mon p1 p2 p3|

	mon := Monitor new.

	p1 := [
	     10 timesRepeat:[
		 Delay waitForSeconds:0.3.
		 mon enter.
		 'p1 got it' printNL.
		 Delay waitForSeconds:0.3.
		 'p1 leaves' printNL.
		 mon exit
	     ]
	] fork.

	p2 := [
	     20 timesRepeat:[
		 Delay waitForSeconds:0.2.
		 mon enter.
		 'p2 got it' printNL.
		 Delay waitForSeconds:0.2.
		 'p2 leaves' printNL.
		 mon exit
	     ]
	] fork.

	p3 := [
	     30 timesRepeat:[
		 Delay waitForSeconds:0.1.
		 mon enter.
		 'p3 got it' printNL.
		 Delay waitForSeconds:0.1.
		 'p3 leaves' printNL.
		 mon exit
	     ]
	] fork.
						[exEnd]
"
! !

!Monitor class methodsFor:'instance creation'!

new
    ^ self basicNew initialize
! !

!Monitor methodsFor:'enter & leave'!

enter
    "enter the monitor"

    |thisProcess wasBlocked|

    thisProcess := Processor activeProcess.

    "
     this works only since interrupts are only serviced at 
     message send and method-return time ....
     If you add a message send into the ifTrue:-block, things will
     go mad ... (especially be careful when adding a debugPrint-here)
    "
    owningProcess isNil ifTrue:[
        count := 1.
        owningProcess := thisProcess.
        ^ self
    ].

    owningProcess == thisProcess ifTrue:[
        count := count + 1.
        ^ self
    ].

    owningProcess isDead ifTrue:[
        'Java [warning]: entering monitor owned by dead process' infoPrintCR.
        "/ self halt.
        owningProcess := thisProcess.
        count := 1.
        ^ self
    ].

    wasBlocked := OperatingSystem blockInterrupts.
    [
        [owningProcess notNil] whileTrue:[
            thisProcess state:#monWait.
            (sema waitWithTimeout:10) isNil ifTrue:[
                (owningProcess notNil and:[owningProcess isDead]) ifTrue:[
                    'Monitor [warning]: aquire monitor from dead process' errorPrintCR.
                    owningProcess := nil.
                ]
            ]
        ].
        count := 1.
        owningProcess := thisProcess.
    ] valueOnUnwindDo:[
        wasBlocked ifFalse:[OperatingSystem unblockInterrupts]
    ]

    "Modified: / 11.12.1998 / 12:38:48 / cg"
!

exit
    "exit the monitor"

    |thisProcess|

    count == 0 ifTrue:[
	'MONITOR [info]: already left' errorPrintCR.
	^ self
    ].

    thisProcess := Processor activeProcess.

    "
     this works only since interrupts are only serviced at 
     message send and method-return time ....
     If you add a message send into the ifTrue:-block, things will
     go mad ... (especially be careful when adding a debugPrint-here)
    "
    owningProcess ~~ thisProcess ifTrue:[
	self halt:'invalid exit'
    ].

    count := count - 1.
    count ~~ 0 ifTrue:[ ^ self].

    owningProcess := nil.
    sema signal.

    "Modified: 21.8.1997 / 16:44:17 / cg"
! !

!Monitor methodsFor:'initialization'!

initialize
    sema := Semaphore new name:'monitorSema'.
    count := 0.

    "Created: 3.5.1996 / 17:24:59 / cg"
! !

!Monitor methodsFor:'queries'!

isFree
    "return true, if the monitor is free
     (i.e. noone waits and count is zero)"

    |wasBlocked ret|

    ret := true.

    wasBlocked := OperatingSystem blockInterrupts.
    owningProcess notNil ifTrue:[
	ret := false
    ] ifFalse:[
	sema numberOfWaitingProcesses ~~ 0 ifTrue:[ret := false].
    ].
    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
    ^ ret.

    "Created: 3.5.1996 / 18:08:38 / cg"
! !

!Monitor class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/Monitor.st,v 1.11 1998-12-11 11:57:54 cg Exp $'
! !