Event triggers, smart semaphores?

Bob Arning arning at charm.net
Sat May 29 17:58:30 UTC 1999


On Fri, 28 May 1999 10:17:46 +0930 "Peter Smet" <peter.smet at flinders.edu.au> wrote: 
>It would be good to have a "smart semaphore" that forced
>outside callers to wait, but let self invoke multiple invocations
>of a message. I would appreciate it if someone could point
>out some code to identify if the invoker of the currently
>executing message is self or not.....

Hi Peter,

You could try something like the code below.

Cheers,
Bob

'From Squeak 2.3 of January 14, 1999 on 29 May 1999 at 1:53:30 pm'!
"Change Set:		RecursiveSema
Date:			29 May 1999
Author:			Bob Arning

I am a variation of the conventional Semaphore that allows consecutive waits without intervening signals to proceed as long as the process which issues the subsequent waits is the one which issued the first wait. This will permit recursive (or other) routines to exclude other processes from a block of code while allowing the current process to keep running. As soon as the number of signals equals the number of waits, another process may proceed.

Test examples are included as class methods."!

Object subclass: #RecursiveSemaphore
	instanceVariableNames: 'holdingProcess waitCount semaphore '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-Processes'!

!RecursiveSemaphore commentStamp: '<historical>' prior: 0!
I am a variation of the conventional Semaphore that allows consecutive waits without intervening signals to proceed as long as the process which issues the subsequent waits is the one which issued the first wait. This will permit recursive (or other) routines to exclude other processes from a block of code while allowing the current process to keep running. As soon as the number of signals equals the number of waits, another process may proceed.

Test examples are included as class methods.!

!RecursiveSemaphore methodsFor: 'as yet unclassified' stamp: 'RAA 5/29/1999 13:27'!
critical: mutuallyExcludedBlock 
	"Evaluate mutuallyExcludedBlock only if the receiver is not currently in 
	the process of running the critical: message. If the receiver is, evaluate 
	mutuallyExcludedBlock after the other critical: message is finished."

	| blockValue |
	self wait.
	blockValue _ mutuallyExcludedBlock value.
	self signal.
	^blockValue! !

!RecursiveSemaphore methodsFor: 'as yet unclassified' stamp: 'RAA 5/29/1999 13:14'!
forMutualExclusion

	semaphore _ Semaphore forMutualExclusion.
	waitCount _ 0.! !

!RecursiveSemaphore methodsFor: 'as yet unclassified' stamp: 'RAA 5/29/1999 13:20'!
signal

	waitCount _ waitCount - 1.
	waitCount <= 0 ifTrue: [
		holdingProcess _ nil.
		waitCount _ 0.
		semaphore signal
	].
! !

!RecursiveSemaphore methodsFor: 'as yet unclassified' stamp: 'RAA 5/29/1999 13:12'!
wait

	holdingProcess == Processor activeProcess ifFalse: [
		semaphore wait.
		waitCount _ 0.
		holdingProcess _ Processor activeProcess.
	].
	waitCount _ waitCount + 1.
! !


!RecursiveSemaphore class reorganize!
('instance creation' forMutualExclusion)
('test example' reportAndWait: test test1: test2: test3: test4:)
!


!RecursiveSemaphore class methodsFor: 'instance creation' stamp: 'RAA 5/29/1999 13:14'!
forMutualExclusion

	^self new forMutualExclusion! !

!RecursiveSemaphore class methodsFor: 'test example' stamp: 'RAA 5/29/1999 13:04'!
reportAndWait: aString

	Transcript show: 'process = ',Processor activeProcess hash printString,
			'  method = ',aString; cr.
	(Delay forSeconds: 1) wait.
! !

!RecursiveSemaphore class methodsFor: 'test example' stamp: 'RAA 5/29/1999 13:34'!
test
"
RecursiveSemaphore test
"
	| semaphore |
	semaphore _ self forMutualExclusion.
	3 timesRepeat: [self test1: semaphore].! !

!RecursiveSemaphore class methodsFor: 'test example' stamp: 'RAA 5/29/1999 13:34'!
test1: semaphore

	[
		self reportAndWait: 'test1'.
		self test2: semaphore.
	] fork.! !

!RecursiveSemaphore class methodsFor: 'test example' stamp: 'RAA 5/29/1999 13:35'!
test2: semaphore

	semaphore critical: [
		self reportAndWait: 'test2'.
		self test3: semaphore.
	].! !

!RecursiveSemaphore class methodsFor: 'test example' stamp: 'RAA 5/29/1999 13:35'!
test3: semaphore

	semaphore critical: [
		self reportAndWait: 'test3'.
		self test4: semaphore.
	].! !

!RecursiveSemaphore class methodsFor: 'test example' stamp: 'RAA 5/29/1999 13:35'!
test4: semaphore

	semaphore critical: [
		self reportAndWait: 'test4'.
	].! !





More information about the Squeak-dev mailing list