mip@massormetrix.ida.liu.se (Mikael Patel) (10/07/89)
Hi, Smalltalkers out there, here are some more examples. This time 
some of the abstractions that are used in concurrent programming:
* Monitor: methods are executed under mutual exculusion
* Condition: synchronization variables within a monitor
* SharedObject: multiple readers or one writer
* UnboundedBuffer: classical monitor example
The implementation follows more or less directly the specification
found in books like M.Ben-Ari, Principles of Concurrent Programming,
Prentice-Hall, 1982.
They are excellent for demonstrating problems with combinding object-
oriented programming with concurrency. Especially that monitors can not
be inherited (super class) and monitor-to-monitor messages give dead-locks.
Mikael R.K. Patel
Researcher and Lecturer
Computer Aided Design Laboratory
Department of Computer and Information Science
Linkoping University, S-581 83  LINKOPING, SWEDEN
Phone: +46 13281821
Telex: 8155076 LIUIDA S			Telefax: +46 13142231
Internet: mip@ida.liu.se		UUCP: ...!sunic!liuida!mip
Bitnet: MIP@SELIUIDA			SUNET: LIUIDA::MIP
 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - 
Object subclass: #Condition
	instanceVariableNames: 'monitor synchronize waiting '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Concurrent-Programming'!
!Condition methodsFor: 'synchronizing'!
signal
	"Check if there are waiting processes. Signal and wait for monitor 
	again "
	waiting > 0
		ifTrue: 
			[synchronize signal.
			monitor waitForSignal]!
wait
	"Wait for condition signal. Check if there are waiting signalers"
	waiting _ waiting + 1.
	monitor waitingForSignal > 0
		ifTrue: [monitor signalWaitingForSignal]
		ifFalse: [monitor signalMutualExculsion].
	synchronize wait.
	waiting _ waiting - 1.! !
!Condition methodsFor: 'initialization'!
initiate: aMonitor 
	"Initiate a newly create condition in the given monitor environment"
	waiting _ 0.
	monitor _ aMonitor.
	synchronize _ Semaphore new! !
!Condition methodsFor: 'accessing'!
waiting
	"Return number of waiting processes"
	^waiting! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
Condition class
	instanceVariableNames: ''!
!Condition class methodsFor: 'instance creation'!
in: aMonitor 
	"Create a new conditon in the given monitor"
	^super new initiate: aMonitor! !
Object subclass: #Monitor
	instanceVariableNames: 'mutex urgent '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Concurrent-Programming'!
!Monitor methodsFor: 'initialization'!
initiate
	" Create a new abstract monitor with mutual exclusion and 
	synchronization condition"
	mutex _ Semaphore forMutualExclusion.
	urgent _ Condition in: self! !
!Monitor methodsFor: 'method-protocol'!
enter
	"Pre-protocol to a monitor method"
	mutex wait!
exit
	"Post-protocol for monitor methods"
	urgent waiting > 0
		ifTrue: [urgent signal]
		ifFalse: [mutex signal]! !
!Monitor methodsFor: 'synchronization'!
signalMutualExculsion
	"External signaling for mutual execulsion"
	mutex signal!
signalWaitingForSignal
	"Signal waiting process which has passed on control"
	urgent signal!
waitForSignal
	"Wait for signal when activated process waiting for signal"
	urgent wait!
waitingForSignal
	"Returns number of waiting signalers"
	^urgent waiting! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
Monitor class
	instanceVariableNames: ''!
!Monitor class methodsFor: 'instance creation'!
new
	"Create a new instance of the monitor and initiate it"
	^super new initiate! !
Monitor subclass: #SharedObject
	instanceVariableNames: 'readers writers okToRead okToWrite '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Concurrent-Programming'!
!SharedObject methodsFor: 'transactions'!
releaseAfterRead
	"Release the shared object after reading"
	self enter.
	readers _ readers - 1.
	readers = 0 ifTrue: [okToWrite signal].
	self exit!
releaseAfterWrite
	"Release the shared object after writing"
	self enter.
	writers _ false.
	okToRead signal.
	self exit!
siezeToRead
	"Seize the shared object for reading. Uses cascaded wakeup of waiting readers"
	self enter.
	writers ifTrue: [okToRead wait. okToRead signal].
	readers _ readers + 1.
	self exit!
siezeToWrite
	"Seize the shared object for writing"
	self enter.
	(readers > 0 or: [writers]) ifTrue: [okToWrite wait].
	writers _ true.
	self exit! !
!SharedObject methodsFor: 'initialization'!
initiate
	"Initiate a shared object"
	super initiate.
	readers _ 0.
	writers _ false.
	okToRead _ Condition in: self.
	okToWrite _ Condition in: self.! !
!SharedObject methodsFor: 'private'!
testing
	S _ SharedObject new.
	S inspect.
	S siezeToRead.
	S siezeToWrite.
	S releaseAfterWrite.
	S releaseAfterRead.! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
SharedObject class
	instanceVariableNames: ''!
!SharedObject class methodsFor: 'instance creation'!
new
	"Create a new shared object instance and initiate it"
	^super new initiate! !
Monitor subclass: #UnboundedBuffer
	instanceVariableNames: 'items notEmpty '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Concurrent-Programming'!
!UnboundedBuffer methodsFor: 'initialization'!
initiate
	"Initiate the monitor (super class) and the buffer and condition"
	super initiate.
	items _ OrderedCollection new.
	notEmpty _ Condition in: self.! !
!UnboundedBuffer methodsFor: 'private'!
testing
	"A simple test of the unbounded buffer"
	B _  UnboundedBuffer new.
	B append: 100.
	B take.
	B inspect.! !
!UnboundedBuffer methodsFor: 'transactions'!
append: anItem
	"Append an item to the buffer"
	self enter.
	items addLast: anItem.
	self exit.!
take
	"Take an item from the buffer if available else wait until not empty"
	| anItem |
	self enter.
	items isEmpty ifTrue: [notEmpty wait].
	anItem _ items removeFirst.
	self exit.
	^anItem! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
UnboundedBuffer class
	instanceVariableNames: ''!
!UnboundedBuffer class methodsFor: 'instance creation'!
new
	"Create a new instance and initiate it"
	^super new initiate! !