AbsTime.st
author Claus Gittinger <cg@exept.de>
Tue, 08 Oct 1996 20:34:08 +0200
changeset 1701 80d13adb2e77
parent 1669 4951596746f7
child 2311 88b035dd471a
permissions -rw-r--r--
better errorHandling in readFrom:onError:

"
 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 absolute time values in milliSeconds starting some
    time in the past. 
    (typically, from 1st. Jan 1970, as used in the Unix operating system,
     but other systems may bias the time differently.
     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 comparisons).

    You should not interpret the osTime instance variable directly, instead
    (if at all), as the OS to convert.

    Its implementation is not the same as in ST-80 
    (which represents Time as seconds from 1. Jan 1901.)

    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.

    [author:]
        Claus Gittinger

    [See also:]
        Time Date
        Delay ProcessorScheduler
"
! !

!AbsoluteTime  class methodsFor:'instance creation'!

day:d month:m year:y hour:h minutes:min seconds:s
    "return an instance of the receiver, given individual components.
     See also `AbsoluteTime now' and other protocol inherited
     from my superclass."

    ^ self 
        day:d month:m year:y hour:h 
        minutes:min seconds:s milliseconds:0

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

    "Modified: 1.7.1996 / 15:22:26 / cg"
!

day:d month:m year:y hour:h minutes:min seconds:s milliseconds:millis
    "return an instance of the receiver, given individual components.
     See also `AbsoluteTime now' and other protocol inherited
     from my superclass."

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

    "
     AbsoluteTime day:2 month:1 year:1991 hour:12 minutes:30 seconds:0 
     AbsoluteTime day:2 month:1 year:1991 hour:12 minutes:30 seconds:0 milliseconds:100
    "

    "Created: 1.7.1996 / 14:46:09 / cg"
    "Modified: 1.7.1996 / 15:22:07 / cg"
!

fromDate:aDate andTime:aTime
    "return an instance of the receiver, initialized from a time and a date
     object.
     See also `AbsoluteTime now' and other protocol inherited
     from my superclass."

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

    "
     AbsoluteTime fromDate:(Date today) andTime:(Time now)  
     AbsoluteTime fromDate:(Date today plusDays:1) andTime:(Time now) 
     AbsoluteTime now 
    "

    "Modified: 8.9.1995 / 15:07:30 / claus"
    "Modified: 19.4.1996 / 15:25:46 / cg"
!

newDay:dayInYear year:year
    "return a new AbsoluteTime, given the year and the day-in-year (starting at 1).
     Date protocol compatibility"

    ^ (Date newDay:dayInYear year:year) asAbsoluteTime

    "
     AbsoluteTime newDay:183 year:1996
    "

    "Modified: 2.7.1996 / 09:39:30 / cg"
!

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

    ErrorSignal handle:[:ex |
        ^ exceptionBlock value
    ] do:[
        |str day month year hour min sec millis ex|

        str := aStringOrStream readStream.

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

        [str peek isDigit] whileFalse:[str next].
        month := Integer readFrom:str onError:ex.
        (month between:1 and:12) ifFalse:[^ exceptionBlock 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:[^ exceptionBlock value].

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

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

        str peek = '.' ifTrue:[
            str next.
            millis := Integer readFrom:str onError:ex.
        ] ifFalse:[
            millis := 0.
        ].

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

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

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

    "Modified: 8.10.1996 / 19:25:59 / 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 
    "

    "Modified: 1.7.1996 / 15:23:02 / cg"
!

dayInWeek
    "return the week-day of the receiver - 1 for monday, 7 for sunday"

    |info|

    info := OperatingSystem computeTimeAndDateFrom:osTime.
    ^ info at:11

    "
     AbsoluteTime now dayInWeek 
    "

    "Modified: 2.7.1996 / 09:20:32 / cg"
    "Created: 2.7.1996 / 09:35:48 / cg"
!

dayInYear
    "return the year-day of the receiver - 1 for Jan, 1st."

    |info|

    info := OperatingSystem computeTimeAndDateFrom:osTime.
    ^ info at:10

    "
     AbsoluteTime now dayInYear  
     AbsoluteTime newDay:184 year:1996  
    "

    "Modified: 2.7.1996 / 10:21:02 / cg"
!

hour
    "return the hour (0..23).
     ST-80 Timestamp compatibility (I'd prefer the name #hours, for Time compatibility)."

    ^ self hours

    "Created: 1.7.1996 / 15:14:50 / cg"
    "Modified: 1.7.1996 / 15:15:32 / cg"
!

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

    |hr|

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

    "
     AbsoluteTime now hours 
    "

    "Modified: 2.7.1996 / 09:20:32 / cg"
!

millisecond
    "return the millisecond (0..999).
     ST-80 Timestamp compatibility (I'd prefer the name #milliseconds)."

    ^ self milliseconds

    "Created: 1.7.1996 / 15:14:50 / cg"
    "Modified: 1.7.1996 / 15:15:24 / cg"
!

milliseconds
    "return the milliseconds (0..999)"

    |m|

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

    "
     AbsoluteTime now milliseconds   
    "

    "Created: 1.7.1996 / 15:15:02 / cg"
    "Modified: 2.7.1996 / 09:21:41 / cg"
!

minute
    "return the minute (0..59).
     ST-80 Timestamp compatibility (I'd prefer the name #minutes, for Time compatibility)."

    ^ self minutes

    "Created: 1.7.1996 / 15:14:29 / cg"
    "Modified: 1.7.1996 / 15:15:37 / cg"
!

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

    |m|

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

    "
     AbsoluteTime now minutes 
    "

    "Modified: 2.7.1996 / 09:20:49 / cg"
!

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
    "

    "Modified: 1.7.1996 / 15:23:05 / cg"
!

second
    "return the second (0..59).
     ST-80 Timestamp compatibility (I'd prefer the name #seconds, for Time compatibility)."

    ^ self seconds

    "Created: 1.7.1996 / 15:14:19 / cg"
    "Modified: 1.7.1996 / 15:15:49 / cg"
!

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

    |s|

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

    "
     AbsoluteTime now seconds 
    "

    "Modified: 2.7.1996 / 09:20:54 / cg"
!

utcOffset
    "return the difference between UTC (Greenwich Mean Time) and the local time
     if daylight saving time applies to ourself, take that into account.
     Add utcOffset bevor converting to get UTC-Time resp. UTC-Date.
    "

    ^ (OperatingSystem computeTimeAndDateFrom:osTime) at:7

    "
     AbsoluteTime now utcOffset 
     (AbsoluteTime day:1 month:7 year:1995 hour:12 minutes:0 seconds:0) utcOffset
    "

    "Modified: 20.12.1995 / 17:28:49 / stefan"
    "Modified: 1.7.1996 / 15:21:29 / cg"
!

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
    "

    "Modified: 1.7.1996 / 15:23:08 / cg"
! !

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

    ^ self getMilliseconds < aTime getMilliseconds

    "Modified: 3.7.1996 / 13:10:17 / cg"
!

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

    (aTime species == self species) ifFalse:[^ false].
    ^ (self getMilliseconds = aTime getMilliseconds)

    "Modified: 3.7.1996 / 13:10:24 / cg"
!

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

    ^ self getMilliseconds > aTime getMilliseconds

    "Modified: 1.7.1996 / 15:24:38 / cg"
!

hash
    "return an integer useful for hashing on times"

    ^ osTime // 1000

    "Modified: 3.7.1996 / 13:10:52 / cg"
! !

!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 mil d m y|

    OperatingSystem computeDatePartsOf:osTime for:[
        :year :month :day | d := day. m := month. y := year.
    ].
    OperatingSystem computeTimePartsOf:osTime for:[
        :hours :minutes :secs :millis | h := hours. min := minutes. s := secs. mil := millis
    ].
    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.
    mil ~~ 0 ifTrue:[
        aStream nextPut:$..
        mil printOn:aStream leftPaddedTo:3 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.        

     Time now asAbsoluteTime printOn:Transcript. Transcript cr.           
     AbsoluteTime now printOn:Transcript. Transcript cr. 

     Date today asAbsoluteTime printOn:Transcript. Transcript cr.           
     Date today printOn:Transcript. Transcript cr.           
    "

    "Modified: 1.7.1996 / 15:20:59 / cg"
!

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

fromOSTime:anUninterpretedOSTime
    "strictly private: set the seconds from an OS time (since whatever)"

    osTime := anUninterpretedOSTime

    "Created: 1.7.1996 / 14:33:21 / cg"
!

getMilliseconds
    "strictly private: return the milliseconds (since whatever)"

    ^ osTime

    "Created: 1.7.1996 / 14:33:56 / cg"
!

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

    ^ osTime // 1000

    "Modified: 1.7.1996 / 14:33:44 / cg"
!

setMilliseconds:millis
    "strictly private: set the milliseconds (since whatever)"

    osTime := millis.

    "Modified: 20.12.1995 / 11:46:36 / stefan"
    "Created: 1.7.1996 / 14:34:24 / cg"
!

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

    osTime := secs * 1000.

    "Modified: 20.12.1995 / 11:46:36 / stefan"
    "Modified: 1.7.1996 / 14:34:10 / cg"
! !

!AbsoluteTime  class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Attic/AbsTime.st,v 1.30 1996-10-08 18:33:36 cg Exp $'
! !