AbstractTime.st
author Claus Gittinger <cg@exept.de>
Thu, 07 Dec 1995 22:32:39 +0100
changeset 699 12f456343eea
parent 528 a083413dfbe8
child 1227 e89b39909085
permissions -rw-r--r--
checkin from browser

"
 COPYRIGHT (c) 1995 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.
"

Magnitude subclass:#AbstractTime
	 instanceVariableNames:''
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Magnitude-General'
!

!AbstractTime class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1995 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
"
    This is an abstract class; there are no instances in the system.
    It is meant as a home for methods common to time handling classes.
"
! !

!AbstractTime class methodsFor:'instance creation'!

dateAndTimeNow
    "return an array filled with date and time"

    ^ Array with:(Date today) with:(Time now)

    "
     Time dateAndTimeNow
    "
!

fromOSTime:osTime
    "return a time, representing the time given by the operatingSystem time.
     Not meant for public use."

    |low hi|

    "now migrating to support LargeInteger OS-time handles ...
     ... in the meantime, support both formats."

    (osTime isMemberOf:Array) ifTrue:[
	low := osTime at:1.
	hi :=  osTime at:2.
    ] ifFalse:[
	low := osTime bitAnd:16rFFFF.
	hi := (osTime bitShift:-16) bitAnd:16rFFFF.
    ].
    ^ self basicNew fromOSTimeLow:low and:hi
!

fromOSTimeLow:osTimeLow and:osTimeHigh
    "return a time, representing the time given by the operatingSystem time.
     Not meant for public use."

    ^ self basicNew fromOSTimeLow:osTimeLow and:osTimeHigh
!

fromSeconds:seconds
    "return an instance that is constructed from seconds.
     This method is only allowed for second values as returned by
     getSeconds, possibly adding/subtracting to that. Never
     depend on any specific interpretation of the seconds."

   ^ self basicNew setSeconds:seconds

    "
     Time fromSeconds:0             should return midnight
     AbsoluteTime fromSeconds:0     on UNIX: returns 1st. Jan 1970
				    on others: dont know
    "
!

now
    "return an instance of myself representing this moment"

    ^ self basicNew fromOSTime:(OperatingSystem getTimeParts)

    "
     AbsoluteTime now   
     Time now   
    "
! !

!AbstractTime class methodsFor:'ST-80 compatibility'!

totalSeconds
    "returns an internal second clock. Dont interpret the returned
     value - if at all, use it to compute time deltas, by subtracting
     returned values."

    ^ self secondClock
! !

!AbstractTime class methodsFor:'obsolete'!

fromUnixTimeLow:low and:hi
    "return an instance of myself, given the unix time.
     Internal interface - not for public use."

    ^ self fromOSTimeLow:low and:hi
! !

!AbstractTime class methodsFor:'queries'!

millisecondClockValue
    "return the millisecond clock - since this one overruns
     regularly, use the value only for short timing deltas.
     Also remember that it wraps when compares these values."

    ^ OperatingSystem getMillisecondTime.

    "
     Time millisecondClockValue 
    "
!

secondClock
    "return seconds of now - for GNU-ST compatibility"

    ^ OperatingSystem getTime

    "
     AbstractTime secondClock    
    "
! !

!AbstractTime class methodsFor:'timing evaluations'!

millisecondsToRun:aBlock
    "evaluate the argument, aBlock; return the number of milliseconds it took"

    |startTime endTime|

    startTime := self millisecondClockValue.
    aBlock value.
    endTime := self millisecondClockValue.
    ^ endTime - startTime

    "
     Time millisecondsToRun:[100 factorial]  
    "
!

secondsToRun:aBlock
    "evaluate the argument, aBlock; return the number of seconds it took"

    |startTime endTime|

    startTime := self secondClock.
    aBlock value.
    endTime := self secondClock.
    ^ endTime - startTime

    "
     Time secondsToRun:[1000 factorial]  
    "
! !

!AbstractTime methodsFor:'accessing'!

hourInDay
    "return the hours (0..23)"

    ^ self hours

    "
     AbsoluteTime now hourInDay 
     Time now hourInDay 
    "
!

minuteInDay
    "return the minutes (0..59)"

    ^ self minutes.

    "
     AbsoluteTime now minuteInDay 
     Time now minuteInDay 
    "
!

secondDay
    "return the seconds (0..59)"

    ^ self seconds

    "
     AbsoluteTime now secondInDay 
     Time now seconds 
    "
! !

!AbstractTime methodsFor:'arithmetic'!

- aTime
    "return the delta in seconds between 2 times."

    ^ self getSeconds - (aTime getSeconds)

    "
     |t1 t2|

     t1 := AbsoluteTime now.
     (Delay forSeconds:5) wait.
     t2 := AbsoluteTime now.
     'seconds passed: ' print. (t2 - t1) printNL.
    "
!

addHours:numberOfHours
    "return a new instance of myself, numberOfHours afterwards."

    ^ self addSeconds:(numberOfHours * (60 * 60))

    "
     |t|

     t := AbsoluteTime now.
     t printNL.
     (t addHours:50) printNL
    "
!

addMinutes:numberOfMinutes
    "return a new instance of myself, numberOfMinutes afterwards."

    ^ self addSeconds:(numberOfMinutes * 60)

    "
     |t|

     t := AbsoluteTime now. t printNL. (t addMinutes:50) printNL

     t := Time now. t printNL. (t addMinutes:50) printNL
    "
!

addSeconds:numberOfSeconds
    "return a new instance of myself, numberOfSeconds afterwards."

    ^ self species basicNew setSeconds:(self getSeconds + numberOfSeconds)

    "
     |t|

     t := AbsoluteTime now. t printNL. (t addSeconds:50) printNL.

     t := Time now. t printNL. (t addSeconds:50) printNL
    "
!

addTime:timeAmount
    "return a new instance of myself, timeAmount seconds afterwards.
     AddTime is a bad name - it does not add a time, but expects
     a number. Use any of addSeconds/addHours etc."

    ^ self species basicNew setSeconds:(self getSeconds + timeAmount)
!

subtractHours:numberOfHours
    "return a new instance of myself, numberOfHours before."

    ^ self subtractSeconds:(numberOfHours * (60 * 60))

    "
     |t|

     t := AbsoluteTime now.
     t printNL.
     (t subtractHours:50) printNL
    "
!

subtractMinutes:numberOfMinutes
    "return a new instance of myself, numberOfMinutes before."

    ^ self subtractSeconds:(numberOfMinutes * 60)

    "
     |t|

     t := AbsoluteTime now.
     t printNL.
     (t subtractMinutes:50) printNL
    "
!

subtractSeconds:numberOfSeconds
    "return a new instance of myself, numberOfSeconds before."

    ^ self species basicNew setSeconds:(self getSeconds - numberOfSeconds)

    "
     |t|

     t := AbsoluteTime now.
     t printNL.
     (t subtractSeconds:50) printNL
    "
!

subtractTime:timeAmount
    "return a new instance opf myself, timeAmount seconds before myself.
     SubtractTime is a bad name - it does not subtract a time, but expects
     a number. Use any of subtractSeconds/subtractHours etc."

    ^ self species basicNew setSeconds:(self getSeconds - timeAmount)
! !

!AbstractTime methodsFor:'private'!

fromOSTime:timeParts
    "set my time, from operatingSystems time parts"

    ^ self fromOSTimeLow:(timeParts at:1) and:(timeParts at:2)
!

fromOSTimeTimeLow:lowTime and:hiTime
    "set my time, from operatingSystems time parts.
     Since I am abstract (not knowing how the time is actually
     represented), this must be done by a concrete class."

    ^ self subclassResponsibility
!

getSeconds
    "get the seconds.
     Since I am abstract (not knowing how the time is actually
     represented), this must be done by a concrete class."

    ^ self subclassResponsibility
!

setSeconds:secs
    "set the seconds.
     Since I am abstract (not knowing how the time is actually
     represented), this must be done by a concrete class."

    ^ self subclassResponsibility
! !

!AbstractTime class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/AbstractTime.st,v 1.8 1995-12-07 21:31:40 cg Exp $'
! !