Timestamp.st
author claus
Mon, 28 Nov 1994 21:34:28 +0100
changeset 213 3b56a17534fd
parent 154 d4236ec280a6
child 241 6f30be88e314
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/Timestamp.st,v 1.7 1994-11-28 20:32:07 claus Exp $
'!

!AbsoluteTime class methodsFor:'documentation'!

copyright
"
 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.
"
!

version
"
$Header: /cvs/stx/stx/libbasic/Timestamp.st,v 1.7 1994-11-28 20:32:07 claus Exp $
"
!

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.
    Actually, the implementation does not even know which time/date the
    OperatingSystem bases its time upon - it is simply keeping the value(s)
    as return from the OS when asked for the time.
    For conversion, these values are given back to the OS, which will know
    how to convert these times.
    This has the advantage, that time-stamps on files (such as last-access-
    time or last-modifiaction-time) can be handled transparent to other
    times (especially comparison).

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

    This class is typically abstract (it does not have to be, though).
    See Time for more details.
"
! !

!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
    "return an instance of Time, given the unix time.
     Internal interface - not for public use."

    ^ 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 := self millisecondClockValue.
    aBlock value.
    endTime := self millisecondClockValue.
    ^ 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).
     Obsolete; use instances of Date for this."

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

    "
     Time now day
    "
!

month
    "return the month of the receiver (1..12).
     Obsolete; use instances of Date for this."

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

    "
     Time now month
    "
!

year
    "return the year of the receiver i.e. 1992.
     Obsolete; use instances of Date for this."

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

    "
     Time now 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
    (aTime species == self species) ifFalse:[^ false].
    ^ (secondsLow == aTime secondsLow) and:[secondsHi == aTime secondsHi]
!

hash
    "return an integer useful for hashing on times"

    ^ (secondsLow bitShift:16) bitOr:secondsLow
! !

!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:'printing & 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
    "return the number of seconds elapsed since whatever time the
     OperatingSystem bases its time upon. Since this is totally
     OS-dependent, do not use this method. (see Time>>asSeconds)"

    ^ (secondsHi * 16r10000) + secondsLow

    "
     AbsoluteTime asSeconds
    "
!

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