Timestamp.st
author Claus Gittinger <cg@exept.de>
Thu, 07 Dec 1995 22:32:39 +0100
changeset 699 12f456343eea
parent 569 7134eb78cf48
child 795 ff477bad0f2d
permissions -rw-r--r--
checkin from browser

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

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

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

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

fromDate:aDate andTime:aTime
    "return an instance of the receiver, initialized from a time and a date
     object."

    ^ self 
	day:aDate day 
	month:aDate month 
	year:aDate year 
	hour:aTime hours 
	minutes:aTime minutes 
	seconds:aTime seconds 

    "
     AbsoluteTime date:Date today time:Time now 
    "

    "Modified: 8.9.1995 / 15:07:30 / claus"
!

readFrom:aStringOrStream onError:exceptionBlock
    "return a new AbsoluteTime, reading a printed representation from aStream.
     The string is interpreted as 24 hour format, as printed.
     Notice, that this is not the storeString format and 
     is different from the format expected by readFrom:."

    |str day month year hour min sec ex|

    str := aStringOrStream readStream.

    ex := [^ exceptionBlock value].
    day := Integer readFrom:str onError:ex.
    (day between:1 and:31) ifFalse:[ex value].

    [str peek isDigit] whileFalse:[str next].
    month := Integer readFrom:str onError:ex.
    (month between:1 and:12) ifFalse:[ex value].

    [str peek isDigit] whileFalse:[str next].
    year := Integer readFrom:str onError:ex.

    [str peek isDigit] whileFalse:[str next].
    hour := Integer readFrom:str onError:ex.
    (hour between:0 and:24) ifFalse:[ex value].

    [str peek isDigit] whileFalse:[str next].
    min := Integer readFrom:str onError:ex.
    (min between:0 and:59) ifFalse:[ex value].

    [str peek isDigit] whileFalse:[str next].
    sec := Integer readFrom:str onError:ex.
    (sec between:0 and:59) ifFalse:[ex value].

    "special check"
    hour == 24 ifTrue:[
	(min ~~ 0 or:[sec ~~ 0]) ifTrue:[ex value].
    ].

    ^ self day:day month:month year:year hour:hour minutes:min seconds:sec

    "
     AbsoluteTime readFrom:'20-2-1995 13:11:06'    
    "

    "Modified: 16.11.1995 / 22:49:39 / cg"
! !

!AbsoluteTime methodsFor:'accessing'!

day
    "return the day-in-month of the receiver (1..31).
     For compatibility, use instances of Date for this."

    |d|

    OperatingSystem computeDatePartsOf:osTime for:[:year :month :day |
	d := day
    ].
    ^ d

    "
     AbsoluteTime now day 
    "
!

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

    |hr|

    OperatingSystem computeTimePartsOf:osTime for:[:hours :minutes :secs |
	hr := hours
    ].
    ^ hr

    "
     AbsoluteTime now hours 
    "

!

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

    |m|

    OperatingSystem computeTimePartsOf:osTime for:[:hours :minutes :secs |
	m := minutes
    ].
    ^ m

    "
     AbsoluteTime now minutes 
    "

!

month
    "return the month of the receiver (1..12).
     For compatibility, use instances of Date for this."

    |m|

    OperatingSystem computeDatePartsOf:osTime for:[ :year :month :day |
	m := month
    ].
    ^ m

    "
     AbsoluteTime now month
    "
!

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

    |s|

    OperatingSystem computeTimePartsOf:osTime for:[:hours :minutes :secs |
	s := secs
    ].
    ^ s

    "
     AbsoluteTime now seconds 
    "

!

year
    "return the year of the receiver i.e. 1992.
     For compatibility, use instances of Date for this."

    |y|

    OperatingSystem computeDatePartsOf:osTime for:[:year :month :day |
	y := year
    ].
    ^ y

    "
     AbsoluteTime now year
    "
! !

!AbsoluteTime methodsFor:'arithmetic'!

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

    ^ self getSeconds - (aTime getSeconds)
!

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

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

!AbsoluteTime methodsFor:'comparing'!

< aTime
    "return true if the argument, aTime is before the receiver"

    |myHi otherHi|

    myHi := self secondsHi. 
    otherHi := aTime secondsHi.
    myHi < otherHi ifTrue:[^ true].
    myHi > otherHi ifTrue:[^ false].
    ^ self secondsLow < aTime secondsLow
!

= aTime
    "return true if the argument, aTime represents the same time"

    (aTime species == self species) ifFalse:[^ false].
    ^ (self secondsLow == aTime secondsLow) and:[self secondsHi == aTime secondsHi]
!

> aTime
    "return true if the argument, aTime is after the receiver"

    |myHi otherHi|

    myHi := self secondsHi. 
    otherHi := aTime secondsHi.
    myHi > otherHi ifTrue:[^ true].
    myHi < otherHi ifTrue:[^ false].
    ^ self secondsLow > aTime secondsLow
!

hash
    "return an integer useful for hashing on times"

    ^ self getSeconds
! !

!AbsoluteTime methodsFor:'converting'!

asAbsoluteTime
    "return an AbsoluteTime object from the receiver - thats the receiver."

    ^ self
!

asDate
    "return a Date object from the receiver.
     The returned date will only represent the day - not the timeOfDay."

    ^ Date fromOSTime:osTime 

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

!

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

    ^ self getSeconds

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

asTime
    "return a Time object from the receiver.
     The returned time will only represent the timeOfDay - not the day."

    ^ Time fromOSTime:osTime

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

!AbsoluteTime methodsFor:'printing & storing'!

printOn:aStream
    "append a user readable representation of the receiver to aStream.
     The format is compatible with readFromString:, but not with readFrom:."

    |h min s d m y|

    OperatingSystem computeDatePartsOf:osTime for:[
	:year :month :day | d := day. m := month. y := year.
    ].
    OperatingSystem computeTimePartsOf:osTime 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 printOn:Transcript. Transcript cr. 
     (AbsoluteTime fromSeconds:0) printOn:Transcript. Transcript cr.
     Time now printOn:Transcript. Transcript cr.           
     Date today printOn:Transcript. Transcript cr.        
    "
!

storeOn:aStream
    "store the receiver in a format suitable for reconstruction of the
     receiver via readFrom:"

    aStream nextPut:$(; 
	    nextPutAll:self class name; 
	    nextPutAll:' new setSeconds:'.
    self getSeconds storeOn:aStream.
    aStream nextPut:$).

    "
     AbsoluteTime now storeString 

     AbsoluteTime readFrom:(AbsoluteTime now storeString) readStream
    "
! !

!AbsoluteTime methodsFor:'private'!

fromOSTimeLow:secsLow and:secsHi
    "strictly private: set the seconds from an OS time (since whatever)"

    osTime := Array with:secsLow with:secsHi
!

getSeconds
    "strictly private: return the seconds (since whatever)"

    ^ ((osTime at:2) * 16r10000) + (osTime at:1)
!

secondsHi
    "strictly private: return the hi part of the seconds"

    ^ osTime at:2 
!

secondsLow
    "strictly private: return the low part of the seconds"

    ^ osTime at:1
!

setSeconds:secs
    "strictly private: set the seconds (since whatever)"

    osTime := Array with:(secs // 16r10000) with:(secs \\ 16r10000)
!

setSecondsLow:secsLow and:secsHi
    "strictly private: set the seconds (since whatever)"

    osTime := Array with:secsLow with:secsHi
! !

!AbsoluteTime class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Timestamp.st,v 1.18 1995-12-07 21:31:29 cg Exp $'
! !