Time.st
author claus
Fri, 16 Jul 1993 11:39:45 +0200
changeset 1 a27a279701f8
child 3 24d81bf47225
permissions -rw-r--r--
Initial revision

"
 COPYRIGHT (c) 1989-93 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:#Time
       instanceVariableNames:'secondsLow secondsHi'
       classVariableNames:''
       poolDictionaries:''
       category:'Magnitude-General'
!

Time comment:'

COPYRIGHT (c) 1989-93 by Claus Gittinger
              All Rights Reserved

time represents a particular second in a day; since we depend on
unix, the seconds are counted from 1. Jan 1970 NOT as in Smalltalk-80
from 1. Jan 1901; since unix-time is 32 bit which does not fit into
a SmallInteger, we keep low and hi 16bit of the time separately.

%W% %E%
'!

!Time class methodsFor:'instance creation'!

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

    ^ OperatingSystem getTime
!

fromUnixTimeLow:low and:hi
    ^ self basicNew setSecondsLow:low and:hi
!

now
    "return an instance of Time representing this moment"

    ^ self basicNew setSecondsLow:(OperatingSystem getTimeLow)
                              and:(OperatingSystem getTimeHi)
!

millisecondClockValue
    "return the millisecond clock - since this one overruns
     regularly, use only for short timing deltas"

    ^ OperatingSystem getMillisecondTime.
! !

!Time class methodsFor:'timing evaluations'!

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

    |startTime endTime|

    startTime := self now.
    aBlock value.
    endTime := self now.
    ^ endTime - startTime
!

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

    |startTime endTime|

    startTime := OperatingSystem getMillisecondTime.
    aBlock value.
    endTime := OperatingSystem getMillisecondTime.
    ^ endTime - startTime
! !

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

totalSeconds
    ^ self secondClock
! !

!Time methodsFor:'accessing'!

hourInDay
    "return the hour-part"

    |hr|

    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
        :hours :minutes :secs |

        hr := hours
    ].
    ^ hr
!

minuteInDay
    "return the minute-part"

    |m|

    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
        :hours :minutes :secs |

        m := minutes
    ].
    ^ m
!

secondInDay
    "return the second-part"

    |s|

    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
        :hours :minutes :secs |

        s := secs
    ].
    ^ s
! !

!Time methodsFor:'comparing'!

> aTime
    (aTime isMemberOf:Time) ifTrue:[
        (secondsHi > aTime secondsHi) ifTrue:[^ true].
        (secondsHi < aTime secondsHi) ifTrue:[^ false].
        (secondsLow > aTime secondsLow) ifTrue:[^ true].
        ^ false
    ].
    ^ self getSeconds > aTime getSeconds
!

< aTime
    (aTime isMemberOf:Time) ifTrue:[
        (secondsHi < aTime secondsHi) ifTrue:[^ true].
        (secondsHi > aTime secondsHi) ifTrue:[^ false].
        (secondsLow < aTime secondsLow) ifTrue:[^ true].
        ^ false
    ].
    ^ self getSeconds < aTime getSeconds
!

= aTime
    (aTime isMemberOf:Time) ifTrue:[
        ^ ((secondsLow == aTime secondsLow) and:[secondsHi == aTime secondsHi])
    ].
    ^ self getSeconds = aTime getSeconds
! !

!Time methodsFor:'arithmetic'!

- aTime
    "return delta in seconds between 2 times"

    ^ self getSeconds - (aTime getSeconds)
!

addTime:timeAmount
    "return a new Time timeAmount seconds from myself"

    ^Time new setSeconds:(self getSeconds + timeAmount)
!

subtractTime:timeAmount
    "return a new Time timeAmount seconds before myself"

    ^Time new setSeconds:(self getSeconds - timeAmount)
! !

!Time methodsFor:'printing'!

printString
    |aString|

    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
        :hours :minutes :secs |

        aString := hours printString , ':' .
        (minutes < 10) ifTrue:[aString := aString , '0'].
        aString := aString , minutes printString.
        aString := aString , ':'.
        (secs < 10) ifTrue:[aString := aString , '0'].
        aString := aString , secs printString
    ].
    ^ aString
! !

!Time methodsFor:'private'!

secondsLow
    ^ secondsLow
!

secondsHi
    ^ secondsHi
!

getSeconds
    ^ (secondsHi * 16r10000) + secondsLow
!

setSeconds:secs
    secondsHi := secs // 16r10000.
    secondsLow := secs \\ 16r10000
!

setSecondsLow:secsLow and:secsHi
    secondsHi := secsHi.
    secondsLow := secsLow
! !