AbsTime.st
author claus
Fri, 25 Feb 1994 14:00:53 +0100
changeset 56 be0ed17e6f85
parent 54 06dbdeeed4f9
child 77 6c38ca59927f
permissions -rw-r--r--
*** empty log message ***

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

AbsoluteTime comment:'

COPYRIGHT (c) 1989 by Claus Gittinger
              All Rights Reserved

$Header: /cvs/stx/stx/libbasic/Attic/AbsTime.st,v 1.2 1994-02-25 12:53:11 claus Exp $
'!

!AbsoluteTime class methodsFor:'documentation'!

documentation
"
This class represents time values in seconds from 1st. Jan 1970, as
used in the Unix operating system. Its implementation is not the same
as in ST-80 (which represents Time as seconds from 1. Jan 1901.

Since unix-times are 32 bit which does not fit into a SmallInteger, 
we keep low and hi 16bit of the time separately (it could have been implemented
using LargeIntegers though).

This is an abstract class to support Time and Date.
"
! !

!AbsoluteTime class methodsFor:'instance creation'!

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

    ^ OperatingSystem getTime
!

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

    ^ OperatingSystem getMillisecondTime.
!

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

dateAndTimeNow
    "return an array filled with date and time"

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

!AbsoluteTime 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
! !

!AbsoluteTime 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
!

day
    "return the day-in-month of the receiver (1..31)"

    OperatingSystem computeDatePartsOf:secondsLow and:secondsHi
                                   for:[:year :month :day |
        ^ day
    ]

    "Date today day"
!

month
    "return the month of the receiver (1..12)"

    OperatingSystem computeDatePartsOf:secondsLow and:secondsHi
                                   for:[:year :month :day |
        ^ month
    ]

    "Date today month"
!

year
    "return the year of the receiver i.e. 1992"

    OperatingSystem computeDatePartsOf:secondsLow and:secondsHi
                                   for:[:year :month :day |
        ^ year
    ]

    "Date today year"
! !

!AbsoluteTime methodsFor:'comparing'!

> aTime
    secondsHi > aTime secondsHi ifTrue:[^ true].
    secondsHi < aTime secondsHi ifTrue:[^ false].
    ^ secondsLow > aTime secondsLow
!

< aTime
    secondsHi < aTime secondsHi ifTrue:[^ true].
    secondsHi > aTime secondsHi ifTrue:[^ false].
    ^ secondsLow < aTime secondsLow
!

= aTime
    ^ (secondsLow == aTime secondsLow) and:[secondsHi == aTime secondsHi]
! !

!AbsoluteTime methodsFor:'arithmetic'!

- aTime
    "return delta in seconds between 2 times/dates"

    ^ self getSeconds - (aTime getSeconds)
!

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

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

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

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

!AbsoluteTime methodsFor:'storing'!

storeString
    |string|

    string := '(' , self class name , ' new setSecondsLow:'.
    string := string , secondsLow storeString.
    string := string , ' and:' , secondsHi storeString.
    string := string , ')'.
    ^ string
! !

!AbsoluteTime methodsFor:'converting'!

asSeconds
    ^ (secondsHi * 16r10000) + secondsLow
!

asDate
    "return a Date object from the receiver"

    ^ Date fromOSTime:(Array with:secondsLow with:secondsHi) 
!

asTime
    ^ Time fromOSTime:(Array with:secondsLow with:secondsHi)
! !

!AbsoluteTime 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
! !