Delay.st
author claus
Tue, 21 Feb 1995 02:07:07 +0100
changeset 275 a76029ddaa98
parent 202 40ca7cc6fb9c
child 379 5b5a130ccd09
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1993 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:#Delay
	 instanceVariableNames:'millisecondDelta resumtionTime delaySemaphore'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Kernel-Processes'
!

Delay comment:'
COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libbasic/Delay.st,v 1.8 1995-02-21 01:06:12 claus Exp $
'!

!Delay class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1993 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.
"
!

version
"
$Header: /cvs/stx/stx/libbasic/Delay.st,v 1.8 1995-02-21 01:06:12 claus Exp $
"
!

documentation
"
    Instances of Delay are used to suspend the execution of a process 
    (i.e. thread) for some time interval. 
    Delays can be created either for some time-interval (seconds or milliseconds), 
    or for delaying until a specific time has reached.
    Once created, a delay is waited upon with Delay>>wait.

    Notice: due to delays (both within unix AND within Smalltalk itself,
    the resumtion time will ALWAYS be after the actual delay time.
    (i.e. a Delay for n-millis will actually suspend for more than n milliseconds)

    Warning: currently, the implementation does not support delays longer than
    a system specific maximum - future versions may remove this limitation.
    For now, do not use delays longer than the value returned by
	OperatingSystem maximumMillisecondTimeDelta

    Also notice: the clock resolution of the operatingSystem is usually limited
    (1/100, 1/60, 1/50, or even 1/20 of a second). Thus very small delays will
    delay for at least this minimum time interval.

    Check your systems resolution with:

	|d t1 t2 res|

	Processor activeProcess priority:24.
	t1 := Time millisecondClockValue.
	d := Delay forMilliseconds:1.
	100 timesRepeat:[d wait].
	t2 := Time millisecondClockValue.
	res := (OperatingSystem millisecondTimeDeltaBetween:t2 and:t1) // 100.
	Transcript show:'minimum delta is about '; show:res; showCr:' milliseconds'.
	Processor activeProcess priority:8.
"
!

examples 
"
    examples:

	delaying for some time-delta:
	(notice: you cannot use this without time-errors in a loop,
	 since the errors will accumulate; after 5 runs through the loop,
	 more than 5 seconds have passed)

		|d|
		d := Delay forMilliseconds:500.
		10 timesRepeat:[d wait]

	prove:
		|d t1 t2 deltaT|
		d := Delay forMilliseconds:500.
		t1 := Time millisecondClockValue.
		10 timesRepeat:[
		    d wait
		].
		t2 := Time millisecondClockValue.
		deltaT := OperatingSystem millisecondTimeDeltaBetween:t2 and:t1.
		Transcript show:'average delay: '; show:deltaT // 10; showCr:' milliseconds'

	delaying until a specific time is reached:
	(this can be used to fix the above problem)

		|now then t1 t2 deltaT|

		t1 := Time millisecondClockValue.
		now := Time millisecondClockValue.
		10 timesRepeat:[
		    then := OperatingSystem millisecondTimeAdd:now and:1000.
		    (Delay untilMilliseconds:then) wait.
		    now := then
		].
		t2 := Time millisecondClockValue.
		deltaT := OperatingSystem millisecondTimeDeltaBetween:t2 and:t1.
		Transcript show:'average delay: '; show:deltaT // 10; showCr:' milliseconds'

	instead of recreating new delays, you can also reuse it:

		|d now then t1 t2 deltaT|

		t1 := Time millisecondClockValue.
		now := Time millisecondClockValue.
		d := Delay new.
		10 timesRepeat:[
		    then := OperatingSystem millisecondTimeAdd:now and:1000.
		    d resumtionTime:then.
		    d wait.
		    now := then
		].
		t2 := Time millisecondClockValue.
		deltaT := OperatingSystem millisecondTimeDeltaBetween:t2 and:t1.
		Transcript show:'average delay: '; show:deltaT // 10; showCr:' milliseconds'
"
! !

!Delay class methodsFor:'instance creation'!

forMilliseconds:aNumber
    "return a new Delay object for delaying aNumber milliseconds"

    ^ self new delay:aNumber
!

forSeconds:aNumber
    "return a new Delay object for delaying aNumber seconds"

    ^ self new delay:(aNumber * 1000) rounded
!

untilMilliseconds:aMillisecondTime
    "return a new Delay object, that will delay the active process
     until the systems millisecond time has reached aMillisecondTime.
    "

    ^ self new resumtionTime:aMillisecondTime
!

until:anAbsoluteTime
    "return a new Delay object, that will delay the active process
     until the system has reached the time represented by the argument.
     BUG:
	due to the limited range of the millisecondTimer, this can 
	(currently) not be used for long delays. The maximum supported
	delay is returned by OperatingSystem>>maximumMillisecondTimeDelta."

    |numberOfSeconds|

    numberOfSeconds := anAbsoluteTime getSeconds - AbsoluteTime now getSeconds.
    ^ self new delay:numberOfSeconds * 1000
! !

!Delay class methodsFor:'queries'!

millisecondClockValue
    "for ST-80 compatibility"

    ^ Time millisecondClockValue
! !

!Delay methodsFor:'accessing'!

delay:aNumber
    "set the millisecond delta"

    millisecondDelta := aNumber.
    delaySemaphore := Semaphore new.
!

resumtionTime:aMillisecondTime
    "set the resumtion time"

    resumtionTime := aMillisecondTime.
    delaySemaphore := Semaphore new.
!

delaySemaphore
    "return the semaphore used to resume the waiting process"

    ^ delaySemaphore
! !

!Delay methodsFor:'early signalling'!

resume
    "resume the waiter, even if the delay-time has not yet passed."

    |wasBlocked|

    wasBlocked := OperatingSystem blockInterrupts.
    Processor disableSemaphore:delaySemaphore.
    delaySemaphore signal.
    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
! !

!Delay methodsFor:'delaying'!

wait
    "suspend the current process until either the relative time delta
     has passed (if millisecondDelta is non-nil), or the absolute millisecondTime
     has been reached (if resumtionTime non-nil)."

    |wasBlocked|

    Processor activeProcess state:#timeWait.
    wasBlocked := OperatingSystem blockInterrupts.
    millisecondDelta notNil ifTrue:[
	Processor signal:delaySemaphore afterMilliseconds:millisecondDelta.
    ] ifFalse:[
	Processor signal:delaySemaphore atMilliseconds:resumtionTime.
    ].
    delaySemaphore wait.
    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].

    "
     '1' printNewline.
     (Delay forSeconds:10) wait.
     '2' printNewline
    "
! !