Timestamp.st
author claus
Sat, 11 Feb 1995 15:07:56 +0100
changeset 242 0190f298e56c
parent 241 6f30be88e314
child 275 a76029ddaa98
permissions -rw-r--r--
added more addXXX/subtractXXX methods

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

'From Smalltalk/X, Version:2.10.4 on 8-feb-1995 at 12:46:45 pm'!

AbstractTime 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.9 1995-02-11 14:07:56 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.9 1995-02-11 14:07:56 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 depend or even know which time/date 
    the OperatingSystem bases its time upon - it is simply keeping the value(s)
    as return from the OS.
    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 should not be confused with Time (which only represents the
    time within one day). Time instances cannot be used to compare times across
    midnight; instances of AbsoluteTime can.

    See Time for more details.
"
! !

!AbsoluteTime class methodsFor:'instance creation'!

day:d month:m year:y hour:h minutes:min seconds:s
    "return an instance of the receiver"

    ^ self fromOSTime:(OperatingSystem 
			computeTimePartsFromYear:y month:m day:d 
					    hour:h minute:min seconds:s)

    "
     AbsoluteTime day:2 month:1 year:1991 hour:12 minutes:30 seconds:0 
     AbsoluteTime day:8 month:1 year:1995 hour:0 minutes:43 seconds:48 
    "
! !

!AbsoluteTime methodsFor:'private'!

secondsLow
    ^ secondsLow
!

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

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

secondsHi
    ^ secondsHi
!

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

getSeconds
    ^ (secondsHi * 16r10000) + secondsLow
!

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

!AbsoluteTime methodsFor:'accessing'!

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

    ^ self hours

    "
     AbsoluteTime now hours 
    "

!

minuteInDay
    "return the minute-part"

    |m|

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

	m := minutes
    ].
    ^ m

    "
     AbsoluteTime now minuteInDay 
    "

!

secondInDay
    "return the second-part"

    |s|

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

	s := secs
    ].
    ^ s

    "
     AbsoluteTime now secondInDay 
    "

!

day
    "return the day-in-month of the receiver (1..31).
     Obsolete; use instances of Date for this."

    |d|

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

    "
     AbsoluteTime now day 
    "
!

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

    |m|

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

    "
     AbsoluteTime now month
    "
!

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

    |y|

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

    "
     AbsoluteTime now year
    "
!

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

    |hr|

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

	hr := hours
    ].
    ^ hr

    "
     AbsoluteTime now hours 
    "

!

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

    |m|

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

	m := minutes
    ].
    ^ m

    "
     AbsoluteTime now minutes 
    "

!

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

    |s|

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

	s := secs
    ].
    ^ s

    "
     AbsoluteTime now seconds 
    "

! !

!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:'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 interpret the value returned by this method.
     You can use it to add/subtract seconds or get time deltas, though."

    ^ (secondsHi * 16r10000) + secondsLow

    "
     AbsoluteTime now asSeconds
     AbsoluteTime fromSeconds:(AbsoluteTime now asSeconds + 3600) 
     Time hour:23 minutes:33 seconds:0         
     Time fromSeconds:((Time hour:23 minutes:33 seconds:0) asSeconds + 3600) 
    "
!

asDate
    "return a Date object from the receiver"

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

    "
     AbsoluteTime now  
     AbsoluteTime now asDate
     (AbsoluteTime now addTime:3600) asDate 
     (AbsoluteTime now addTime:3600) asTime 
     AbsoluteTime fromSeconds:(AbsoluteTime now asSeconds + 3600) 
     (AbsoluteTime fromSeconds:(AbsoluteTime now asSeconds + 3600)) asDate  
    "

!

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

    "
     AbsoluteTime now  
     AbsoluteTime now asTime
     (AbsoluteTime now addTime:3600) asTime 
    "

! !

!AbsoluteTime methodsFor:'arithmetic'!

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

    ^ self getSeconds - (aTime getSeconds)
!

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

    ^ self class new setSeconds:(self getSeconds + numberOfSeconds)

    "
     |t|

     t := AbsoluteTime now.
     t printNL.
     (t addSeconds: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
    "
!

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

addDays:numberOfDays
    "return a new instance of myself, numberOfDays afterwards."

    ^ self addSeconds:(numberOfDays * (60 * 60 * 24))

    "
     |t|

     t := AbsoluteTime now.
     t printNL.
     (t addDays:7) printNL
    "
!

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

    ^ self class new setSeconds:(self getSeconds - numberOfSeconds)

    "
     |t|

     t := AbsoluteTime now.
     t printNL.
     (t subtractSeconds: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
    "
!

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

subtractDays:numberOfDays
    "return a new instance of myself, numberOfDays before."

    ^ self subtractSeconds:(numberOfDays * (60 * 60 * 24))

    "
     |t|

     t := AbsoluteTime now.
     t printNL.
     (t subtractDays: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 class new setSeconds:(self getSeconds + timeAmount)
!

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 class new setSeconds:(self getSeconds - timeAmount)
! !

!AbsoluteTime methodsFor:'printing & storing'!

printOn:aStream
    |h min s d m y|

    OperatingSystem computeDatePartsOf:secondsLow and:secondsHi for:[
	:year :month :day | d := day. m := month. y := year.
    ].
    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
	:hours :minutes :secs | h := hours. min := minutes. s := secs.
    ].
    d printOn:aStream.
    aStream nextPut:$-.
    m printOn:aStream.
    aStream nextPut:$-.
    y printOn:aStream.
    aStream space.
    h printOn:aStream leftPaddedTo:2 with:$0. 
    aStream nextPut:$:.
    min printOn:aStream leftPaddedTo:2 with:$0.
    aStream nextPut:$:.
    s printOn:aStream leftPaddedTo:2 with:$0.

    "
     AbsoluteTime now 
     AbsoluteTime fromSeconds:0 
     Time now            
     Date today         
    "
!

storeOn:aStream
    aStream nextPut:$(; 
	    nextPutAll:self class name; 
	    nextPutAll:' new setSecondsLow:'.
    secondsLow storeOn:aStream.
    aStream nextPutAll:' and:'.
    secondsHi storeOn:aStream.
    aStream nextPut:$).

    "
     AbsoluteTime now storeString '(AbsoluteTime new setSecondsLow:39757 and:12087)'

     AbsoluteTime readFromString:(AbsoluteTime now storeString) 
    "
! !