Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
implementation of Monitors
Last updated at 12:35 pm UTC on 17 January 2006
Object subclass: #MesaMonitor
instanceVariableNames: 'mutex owner '
classVariableNames: ''
poolDictionaries: ''
category: 'Tool-Monitor'!

MesaMonitor commentStamp: 'C.K.L. 12/1/2003 12:57' prior: 0!

The MesaMonitor class provides mutual exclusion and conditional blocking facilities between threads. This implementation follows a simplified version of the Mesa (Modulo-3) semantics described in Lampson and Redell's 1980 paper "Experience with Processes and Monitors in Mesa". The MesaMonitor class is designed to work with the MesaMonitorCondition class, which provides condition variables that can be signaled or waited on inside the critical regions of the monitor. You generally only need to send the critical: message to use the monitor, as illustrated below:

monitor critical: aBlock "code to be executed in critical region"

Please refer to the MesaMonitorTest class on how to use monitor conditional variables.!


MesaMonitor methodsFor: 'access control' stamp: 'C.K.L. 11/26/2003 01:29'!

clearOwner
owner _ nil! !

MesaMonitor methodsFor: 'access control' stamp: 'C.K.L. 11/26/2003 01:29'!

ensureOwner
(self isOwner)
ifFalse: [ self error: 'Monitor access violation' ]! !

MesaMonitor methodsFor: 'access control' stamp: 'C.K.L. 11/26/2003 01:29'!

isOwner
^ owner = Processor activeProcess! !

MesaMonitor methodsFor: 'access control' stamp: 'C.K.L. 11/26/2003 01:29'!

setOwner
owner _ Processor activeProcess! !


MesaMonitor methodsFor: 'initialization' stamp: 'C.K.L. 11/26/2003 01:29'!

initialize
mutex _ Semaphore forMutualExclusion.
next _ Semaphore new.
nextn _ 0.
self clearOwner! !

MesaMonitor methodsFor: 'initialization' stamp: 'C.K.L. 12/1/2003 11:47'!

newCondition: aBlock
^ MesaMonitorCondition new initialize: aBlock monitor: self! !


MesaMonitor methodsFor: 'internals' stamp: 'C.K.L. 11/26/2003 01:30'!

monitorEnter
mutex wait.
self setOwner! !

MesaMonitor methodsFor: 'internals' stamp: 'C.K.L. 11/26/2003 01:31'!

monitorEscape
self clearOwner.
mutex signal! !


MesaMonitor methodsFor: 'synchronization' stamp: 'C.K.L. 11/26/2003 01:31'!

critical: aBlock
| value |
self isOwner
ifTrue: [^ aBlock value].
self monitorEnter.
value _ aBlock value.
self monitorEscape.
^ value! !

"– – – – – – – – – – – – – – – – – – "!

MesaMonitor class
instanceVariableNames: ''!

MesaMonitor class methodsFor: 'instance creation' stamp: 'C.K.L. 12/1/2003 11:44'!

new
| instance |
instance _ super new.
instance initialize.
^ instance! !


Object subclass: #MesaMonitorCondition
instanceVariableNames: 'cond condcount condsem mon '
classVariableNames: ''
poolDictionaries: ''
category: 'Tool-Monitor'!

MesaMonitorCondition commentStamp: 'C.K.L. 11/26/2003 01:29' prior: 0!

The MesaMonitorCondition class provides conditional blocking for the monitor implemented by the MesaMonitor class. Instances to MesaMonitorCondition should only be created through the newCondition: message of the MesaMonitor class, which takes a boolean expression enclosed in a block as the argument and returns an instance of MesaMonitorCondition. Threads should only block (by invoking wait) when the expression evaluates to false.

To block the current thread, the program should make sure that the condition is false and then invoke the wait method of the conditional variable. To wake up a thread waiting on a specific conditional variable, make sure that the condition is true and then invoke the signal method of the conditional variable.

Note that access to MesaMonitorCondition methods is not allowed outside of the critical region protected by the associated monitor.!


MesaMonitorCondition methodsFor: 'initialization' stamp: 'C.K.L. 12/1/2003 12:58'!

initialize: aBlock monitor: aMonitor
cond _ aBlock.
condcount _ 0.
condsem _ Semaphore new.
mon _ aMonitor! !


MesaMonitorCondition methodsFor: 'synchronization' stamp: 'C.K.L. 12/1/2003 12:58'!

signal
mon ensureOwner.
(cond value)
ifFalse: [self error: 'monitor semantics violation'].
(condcount > 0)
ifTrue: [condsem signal]! !

MesaMonitorCondition methodsFor: 'synchronization' stamp: 'C.K.L. 12/1/2003 12:58'!

wait
mon ensureOwner.
(cond value)
ifTrue: [self error: 'unnecessary monitor wait'].
condcount _ condcount+1.
mon monitorEscape.
condsem wait.
condcount _ condcount-1.
mon monitorEnter! !


Object subclass: #MesaMonitorTest
instanceVariableNames: 'mon buffer limit iteration rand notFull notEmpty '
classVariableNames: ''
poolDictionaries: ''
category: 'Tool-Monitor'!

MesaMonitorTest commentStamp: 'C.K.L. 11/13/2003 00:37' prior: 0!

This is a straightforward implementation of the bounded-buffer producer-consumer problem that serves as a test for the MesaMonitor and MesaMonitorCondition classes. Correctness of the behavior is established through inspecting the trace outputs.



MesaMonitorTest methodsFor: 'execution' stamp: 'C.K.L. 11/12/2003 23:57'!

consumer: aNumber
| banner delay |
banner _ 'consumer ', (aNumber asString), ': '.
iteration timesRepeat: [
Transcript cr; show: banner, 'entering critical...'.
mon critical: [
Transcript cr; show: ' ', banner, 'entered critical... ', (buffer asString).
[buffer = 0] whileTrue: [
Transcript cr; show: ' ', banner, 'empty!! Suspending...'.
notEmpty wait.
Transcript cr; show: ' ', banner, 'wakes up!! ', (buffer asString)].
delay _ Delay forMilliseconds: (rand nextInt: 100).
delay wait.
buffer _ buffer-1.
Transcript cr; show: ' ', banner, 'signaling #notFull...'.
notFull signal.
Transcript cr; show: ' ', banner, 'exiting critical... ', (buffer asString)].
Transcript cr; show: banner, 'sleeping...'.
delay _ Delay forMilliseconds: (rand nextInt: 100).
delay wait]! !

MesaMonitorTest methodsFor: 'execution' stamp: 'C.K.L. 11/13/2003 00:04'!

producer: aNumber
| banner delay |
banner _ 'producer ', (aNumber asString), ': '.
iteration timesRepeat: [
Transcript cr; show: banner, 'entering critical...'.
mon critical: [
Transcript cr; show: ' ', banner, 'entered critical... ', (buffer asString).
[buffer = limit] whileTrue: [
Transcript cr; show: ' ', banner, 'full!! Suspending...'.
notFull wait.
Transcript cr; show: ' ', banner, 'wakes up!! ', (buffer asString)].
delay _ Delay forMilliseconds: (rand nextInt: 100).
delay wait.
buffer _ buffer+1.
Transcript cr; show: ' ', banner, 'signaling #notEmpty...'.
notEmpty signal.
Transcript cr; show: ' ', banner, 'exiting critical... ', (buffer asString)].
Transcript cr; show: banner, 'sleeping...'.
delay _ Delay forMilliseconds: (rand nextInt: 100).
delay wait]! !

MesaMonitorTest methodsFor: 'execution' stamp: 'C.K.L. 11/13/2003 13:25'!

run
[self consumer: 1] fork.
[self producer: 1] fork.
[self consumer: 2] fork.
[self consumer: 3] fork.
[self producer: 2] fork.
[self producer: 3] fork! !


MesaMonitorTest methodsFor: 'initialization' stamp: 'C.K.L. 12/1/2003 11:45'!

initialize
mon _ MesaMonitor new.
notFull _ mon newCondition: [buffer limit].
notEmpty _ mon newCondition: [buffer > 0].
buffer _ 0.
limit _ 3.
iteration _ 20.
rand _ Random new initialize! !


Object subclass: #Monitor
instanceVariableNames: 'mutex urgent urgentcount owner '
classVariableNames: ''
poolDictionaries: ''
category: 'Tool-Monitor'!

Monitor commentStamp: 'C.K.L. 12/1/2003 12:47' prior: 0!

The Monitor class provides mutual exclusion and conditional blocking facilities between threads. This is a faithful implementation (down to the naming of variables) of the Hoare semantics described in C.A.R. Hoare's 1974 paper "Monitors: An Operating System Structuring Concept". The Monitor class is designed to work with the MonitorCondition class, which provides condition variables that can be signaled or waited on inside the critical regions of the monitor. You generally only need to send the critical: message to use the monitor, as illustrated below:

monitor critical: aBlock "code to be executed in critical region"

Please refer to the MonitorTest class on how to use monitor conditional variables.!


Monitor methodsFor: 'access control' stamp: 'C.K.L. 10/29/2003 15:44'!

clearOwner
owner _ nil! !

Monitor methodsFor: 'access control' stamp: 'C.K.L. 10/29/2003 19:58'!

ensureOwner
(self isOwner)
ifFalse: [ self error: 'Monitor access violation' ]! !

Monitor methodsFor: 'access control' stamp: 'C.K.L. 10/29/2003 19:51'!

isOwner
^ owner = Processor activeProcess! !

Monitor methodsFor: 'access control' stamp: 'C.K.L. 12/1/2003 12:30'!

monitorEscape
(urgentcount > 0)
ifTrue: [urgent signal]
ifFalse: [self clearOwner. mutex signal]! !

Monitor methodsFor: 'access control' stamp: 'C.K.L. 10/29/2003 19:58'!

setOwner
owner _ Processor activeProcess! !


Monitor methodsFor: 'initialization' stamp: 'C.K.L. 12/1/2003 12:29'!

initialize
mutex _ Semaphore forMutualExclusion.
urgent _ Semaphore new.
urgentcount _ 0.
self clearOwner! !

Monitor methodsFor: 'initialization' stamp: 'C.K.L. 11/7/2003 12:06'!

newCondition: aBlock
^ MonitorCondition new initialize: aBlock monitor: self! !


Monitor methodsFor: 'internals' stamp: 'C.K.L. 12/1/2003 12:31'!

signalCondition: aSemaphore
urgentcount _ urgentcount+1.
aSemaphore signal.
urgent wait.
self setOwner.
urgentcount _ urgentcount-1! !


Monitor methodsFor: 'synchronization' stamp: 'C.K.L. 11/7/2003 12:03'!

critical: aBlock
| value |
self isOwner
ifTrue: [^ aBlock value].
mutex wait.
self setOwner.
value _ aBlock value.
self monitorEscape.
^ value! !

"– – – – – – – – – – – – – – – – – – "!

Monitor class
instanceVariableNames: ''!

Monitor class methodsFor: 'instance creation' stamp: 'C.K.L. 12/1/2003 11:56'!

new
| instance |
instance _ super new.
instance initialize.
^ instance! !


Object subclass: #MonitorCondition
instanceVariableNames: 'cond condcount condsem mon '
classVariableNames: ''
poolDictionaries: ''
category: 'Tool-Monitor'!

MonitorCondition commentStamp: 'C.K.L. 11/12/2003 15:32' prior: 0!

The MonitorCondition class provides conditional blocking for the monitor implemented by the Monitor class. Instances to MonitorCondition should only be created through the newCondition: message of the Monitor class, which takes a boolean expression enclosed in a block as the argument and returns an instance of MonitorCondition. Threads should only block (by invoking wait) when the expression evaluates to false.

To block the current thread, the program should make sure that the condition is false and then invoke the wait method of the conditional variable. To wake up a thread waiting on a specific conditional variable, make sure that the condition is true and then invoke the signal method of the conditional variable.

Note that access to MonitorCondition methods is not allowed outside of the critical region protected by the associated monitor.



MonitorCondition methodsFor: 'initialization' stamp: 'C.K.L. 12/1/2003 12:33'!

initialize: aBlock monitor: aMonitor
cond _ aBlock.
condcount _ 0.
condsem _ Semaphore new.
mon _ aMonitor! !


MonitorCondition methodsFor: 'synchronization' stamp: 'C.K.L. 12/1/2003 12:33'!

signal
mon ensureOwner.
(cond value)
ifFalse: [self error: 'monitor semantics violation'].
(condcount > 0)
ifTrue: [mon signalCondition: condsem]! !

MonitorCondition methodsFor: 'synchronization' stamp: 'C.K.L. 12/1/2003 12:33'!

wait
mon ensureOwner.
(cond value)
ifTrue: [self error: 'unnecessary monitor wait'].
condcount _ condcount+1.
mon monitorEscape.
condsem wait.
condcount _ condcount-1.
mon setOwner! !


Object subclass: #MonitorTest
instanceVariableNames: 'mon buffer limit iteration rand notFull notEmpty '
classVariableNames: ''
poolDictionaries: ''
category: 'Tool-Monitor'!

MonitorTest commentStamp: 'C.K.L. 11/12/2003 15:43' prior: 0!

This is a straightforward implementation of the bounded-buffer producer-consumer problem that serves as a test for the Monitor and MonitorCondition classes. Correctness of the behavior is established through inspecting the trace outputs.



MonitorTest methodsFor: 'execution' stamp: 'C.K.L. 11/7/2003 12:06'!

consumer: aNumber
| banner delay |
banner _ 'consumer ', (aNumber asString), ': '.
iteration timesRepeat: [
Transcript cr; show: banner, 'entering critical...'.
mon critical: [
Transcript cr; show: ' ', banner, 'entered critical... ', (buffer asString).
(buffer = 0) ifTrue: [
Transcript cr; show: ' ', banner, 'empty!! Suspending...'.
notEmpty wait.
Transcript cr; show: ' ', banner, 'wakes up!! ', (buffer asString)].
delay _ Delay forMilliseconds: (rand nextInt: 100).
delay wait.
buffer _ buffer-1.
Transcript cr; show: ' ', banner, 'signaling #notFull...'.
notFull signal.
Transcript cr; show: ' ', banner, 'exiting critical... ', (buffer asString)].
Transcript cr; show: banner, 'sleeping...'.
delay _ Delay forMilliseconds: (rand nextInt: 100).
delay wait]! !

MonitorTest methodsFor: 'execution' stamp: 'C.K.L. 11/7/2003 12:06'!

producer: aNumber
| banner delay |
banner _ 'producer ', (aNumber asString), ': '.
iteration timesRepeat: [
Transcript cr; show: banner, 'entering critical...'.
mon critical: [
Transcript cr; show: ' ', banner, 'entered critical... ', (buffer asString).
(buffer = limit) ifTrue: [
Transcript cr; show: ' ', banner, 'full!! Suspending...'.
notFull wait.
Transcript cr; show: ' ', banner, 'wakes up!! ', (buffer asString)].
delay _ Delay forMilliseconds: (rand nextInt: 100).
delay wait.
buffer _ buffer+1.
Transcript cr; show: ' ', banner, 'signaling #notEmpty...'.
notEmpty signal.
Transcript cr; show: ' ', banner, 'exiting critical... ', (buffer asString)].
Transcript cr; show: banner, 'sleeping...'.
delay _ Delay forMilliseconds: (rand nextInt: 100).
delay wait]! !

MonitorTest methodsFor: 'execution' stamp: 'C.K.L. 10/29/2003 22:14'!

run
[self consumer: 1] fork.
[self producer: 1] fork.
[self producer: 2] fork.
[self consumer: 2] fork.
[self consumer: 3] fork.
[self producer: 3] fork! !


MonitorTest methodsFor: 'initialization' stamp: 'C.K.L. 12/1/2003 12:06'!

initialize
mon _ Monitor new.
notFull _ mon newCondition: [buffer limit].
notEmpty _ mon newCondition: [buffer > 0].
buffer _ 0.
limit _ 3.
iteration _ 20.
rand _ Random new initialize! !