Timestamp.st
author Claus Gittinger <cg@exept.de>
Tue, 03 Jun 2003 12:36:51 +0200
changeset 7327 ab17eb5f11a6
parent 7111 3cc2963786e2
child 7466 87775b24d5ea
permissions -rw-r--r--
printFormat

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

"{ Package: 'stx:libbasic' }"

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.

    Notice: this class is aliased as Timestamp for ST-80 compatibility.

    [author:]
	Claus Gittinger

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

!AbsoluteTime class methodsFor:'instance creation'!

UTCYear:y month:m day:d hour:h minute:min second:s millisecond: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 
			computeOSTimeFromUTCYear:y month:m day:d 
					 hour:h minute:min second:s
					 millisecond:millis)

    "
     AbsoluteTime UTCYear:1970 month:1 day:1 hour:1 minute:0 second:0 millisecond:0
     AbsoluteTime UTCYear:1991 month:1 day:2 hour:12 minute:30 second:0 millisecond:0
     AbsoluteTime UTCYear:1991 month:1 day:2 hour:12 minute:30 second:0 millisecond:100
     AbsoluteTime UTCYear:1999 month:7 day:1 hour:1 minute:0 second:0 millisecond:0
     AbsoluteTime UTCYear:2000 month:1 day:1 hour:1 minute:0 second:0 millisecond:0
    "

    "Modified: / 1.7.1996 / 15:22:07 / cg"
    "Created: / 13.7.1999 / 12:34:37 / stefan"
    "Modified: / 13.7.1999 / 12:42:30 / stefan"
!

basicReadFrom:aStringOrStream
    "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:.
     KLUDGE: 
        us and non-us format have different ordering of day and month;
        The format read here is (non-us) dd-mm-yyyy hh:mm:ss.iii
        or (us-format, for Travis) mm/dd/yyyy hh:mm:ss.iii.
     On error, raise an exception"

    |str first second day month year hour min sec millis usFormat|

    str := aStringOrStream readStream.

    first := Integer readFrom:str.

    first > 31 ifTrue:[
        "/ assume iso8601 format;
        ^ self readIso8601FormatFrom:str yearAlreadyRead:first.
    ].

    "/ consider this a kludge
    usFormat := (str peek == $/ ).

    [str peek isDigit] whileFalse:[str next].
    second := Integer readFrom:str.

    usFormat ifTrue:[
        month := first.
        day := second.
    ] ifFalse:[
        month := second.
        day := first.
    ].

    (day between:1 and:31) ifFalse:[ ConversionError raiseErrorString:'bad day' ].
    (month between:1 and:12) ifFalse:[ ConversionError raiseErrorString:'bad month' ].

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

    [str peek isDigit] whileFalse:[str next].
    hour := Integer readFrom:str.
    (hour between:0 and:24) ifFalse:[ ConversionError raiseErrorString:'bad hour' ].

    [str peek isDigit] whileFalse:[str next].
    min := Integer readFrom:str.
    (min between:0 and:59) ifFalse:[ ConversionError raiseErrorString:'bad minute' ].

    str atEnd ifTrue:[
        sec := millis := 0.
    ] ifFalse:[
        [str peek isDigit] whileFalse:[str next].
        sec := Integer readFrom:str.
        (sec between:0 and:59) ifFalse:[ ConversionError raiseErrorString:'bad second' ].

        str peek = $. ifTrue:[
            str next.
            millis := Integer readFrom:str.
            millis >= 1000 ifTrue:[ ConversionError raiseErrorString:'bad millisecond' ].
        ] ifFalse:[
            millis := 0.
        ].
    ].

    "special check - only 24:00:00 is allowed;
     every time after that must wrap"
    hour == 24 ifTrue:[
        (min ~~ 0 or:[sec ~~ 0 or:[millis ~~ 0]]) ifTrue:[ ConversionError raiseErrorString:'bad hour' ].
    ].
    ^ self year:year month:month day:day hour:hour minute:min second:sec millisecond:millis.

    "
     AbsoluteTime basicReadFrom:'20-2-1995 13:11:06'    
     (AbsoluteTime basicReadFrom:'10-9-1995 13:11:06') month   
     (AbsoluteTime basicReadFrom:'10/9/1995 13:11:06') month   
     AbsoluteTime basicReadFrom:'20-2-1995 13:11'       
     AbsoluteTime basicReadFrom:'20-2-1995 13:11:06.100'    
     AbsoluteTime basicReadFrom:'32-2-1995 13:11:06.100'  
     AbsoluteTime basicReadFrom:'32-foo-1995 13:11:06.100' 
     AbsoluteTime basicReadFrom:'20-13-1995 13:11:06.100'   
     AbsoluteTime basicReadFrom:'20-12-1995 25:11:06.100'   
     AbsoluteTime basicReadFrom:'20-12-1995 23:61:06.100'   
     AbsoluteTime basicReadFrom:'20-12-1995 23:10:66.100'   
     AbsoluteTime basicReadFrom:'20-12-1995 23:10:00.1000'   
     AbsoluteTime basicReadFrom:'20-2-1995 24:01:00.100' 
     AbsoluteTime basicReadFrom:'20-2-1995 24:00:01.100' 
     AbsoluteTime basicReadFrom:'foo'                    
     AbsoluteTime basicReadFrom:(AbsoluteTime now printString)                  
     AbsoluteTime basicReadFrom:'1995-10-20 24:00:00.000' 
     AbsoluteTime basicReadFrom:'1995-10-20 12:10:00.000' 
    "
!

day:d month:m year:y hour:h minutes:min seconds:s
    "This is obsolete. User #year:month:day:hour:minute:second:"

    ^ self 
	year:y month:m day:d hour:h 
	minute:min second:s millisecond:0

    "
     AbsoluteTime day:2 month:1 year:1991 hour:12 minute:30 second:0 
     AbsoluteTime day:8 month:1 year:1995 hour:0 minute:43 second:48 
    "

    "Modified: / 1.7.1996 / 15:22:26 / cg"
    "Modified: / 13.7.1999 / 12:29:56 / stefan"
!

day:d month:m year:y hour:h minutes:min seconds:s milliseconds:millis
    "This is obsolete. User #year:month:day:hour:minute:second:millisecond:"

    ^ self year:y month:m day:d hour:h minute:min second:s millisecond:millis

    "
     AbsoluteTime day:1 month:1 year:1970 hour:1 minute:0 second:0 
     AbsoluteTime day:2 month:1 year:1991 hour:12 minute:30 second:0 
     AbsoluteTime day:2 month:1 year:1991 hour:12 minute:30 second:0 millisecond:100
    "

    "Created: / 1.7.1996 / 14:46:09 / cg"
    "Modified: / 1.7.1996 / 15:22:07 / cg"
    "Modified: / 13.7.1999 / 12:30:26 / stefan"
!

decodeFromLiteralArray:anArray
    "decode an AbsoluteTime literalArray.

     anArray may be:
        #(AbsoluteTime '200004182000.123')

     or the deprecated old format, that is not portable between different architectures.
     We parse this for backward compatibility (will be eventually removed).

        #(AbsoluteTime #osTime: 12345678)     
    "

    (anArray at:2) == #osTime: ifTrue:[
        ^ self new osTime:(anArray at:3).
    ].

    ^ self readGeneralizedFrom:(anArray at:2) onError:[self error:'literal array decoding']
!

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 
	year:aDate year 
	month:aDate month 
	day:aDate day 
	hour:aTime hours 
	minute:aTime minutes 
	second: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"
    "Modified: / 13.7.1999 / 12:30:47 / stefan"
!

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:.
     The format read here is dd-mm-yyyy hh:mm:ss.iii"

    |newTime|

    Error handle:[:ex |
        ^ super readFrom:aStringOrStream onError:exceptionBlock 
    ] do:[
        newTime := self basicReadFrom:aStringOrStream.
    ].
    ^ newTime

    "
     AbsoluteTime readFrom:'20-2-1995 13:11:06'                            
     AbsoluteTime readFrom:'20-2-1995 13:11'                               
     AbsoluteTime readFrom:'20-2-2001 13:11'                               
     AbsoluteTime readFrom:'20-2-1995 13:11:06.100'                        
     AbsoluteTime readFrom:'32-2-1995 13:11:06.100' onError:'wrong'        
     AbsoluteTime readFrom:'32-foo-1995 13:11:06.100' onError:'wrong'      
     AbsoluteTime readFrom:'20-2-1995 24:01:00.100' onError:'wrong'        
     AbsoluteTime readFrom:'20-2-1995 24:00:01.100' onError:'wrong'        
     AbsoluteTime readFrom:'2002-08-02 24:00:01.100' onError:'wrong'        
     AbsoluteTime readFrom:'foo' onError:'wrong'                           
     AbsoluteTime readFrom:(AbsoluteTime now storeString) onError:'wrong'                     
    "

    "Modified: / 8.10.1996 / 19:25:59 / cg"
    "Modified: / 13.7.1999 / 12:31:14 / stefan"
!

readGeneralizedFrom: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:.
     The format read here is yyyymmddHHMMSS.iii+uuuu,
     which is the ASN1 GeneralizedTime format."

    |newTime|

    ^ [
        |str day month year hour min sec millis c|

        sec := millis := 0.
        str := aStringOrStream readStream.

        year := Integer readFrom:(str next:4).
        month := Integer readFrom:(str next:2).
        (month between:1 and:12) ifFalse:[^ exceptionBlock value].
        day := Integer readFrom:(str next:2).
        (day between:1 and:31) ifFalse:[^ exceptionBlock value].
        hour:= Integer readFrom:(str next:2).
        (hour between:0 and:24) ifFalse:[^ exceptionBlock value].
        min:= Integer readFrom:(str next:2).
        (min between:0 and:59) ifFalse:[^ exceptionBlock value].
        str atEnd ifFalse:[
            sec := Integer readFrom:(str next:2).
            (sec between:0 and:59) ifFalse:[^ exceptionBlock value].
            str peek == $. ifTrue:[
                str next.
                millis := Integer readFrom:str.
            ].
        ]. 
        str atEnd ifTrue:[
            "/ this is local time
            newTime := self year:year month:month day:day 
                              hour:hour minute:min second:sec millisecond:millis.
        ] ifFalse:[
            c := str next.
            c ~~ $Z ifTrue:[ |tzh tzmin|
                tzh := Integer readFrom:(str next:2).
                tzmin := Integer readFrom:(str next:2).
                c == $+ ifTrue:[
                    "/ add hours and minutes
                    hour := hour + tzh.
                    min := min + tzmin.
                ] ifFalse:[
                    c ~~ $- ifTrue:[
                       self error:'bad time offset'.
                    ].
                    "/ subtract hours and minutes
                    hour := hour - tzh.
                    min := min - tzmin.
                ].
            ].
            "/ this is UTC time
            newTime := self UTCYear:year month:month day:day 
                              hour:hour minute:min second:sec millisecond:millis.
        ].
        newTime
    ] on:Error do:exceptionBlock.

    "
     |s|
     s := '' writeStream.
     AbsoluteTime now printGeneralizedOn:s.
     AbsoluteTime readGeneralizedFrom:s contents onError:[]

     AbsoluteTime readGeneralizedFrom:'20001018000000+0200' onError:[]
     AbsoluteTime readGeneralizedFrom:'20001018000000+0300' onError:[]

     AbsoluteTime readGeneralizedFrom:'20000202000000+0100' onError:[]
     AbsoluteTime readGeneralizedFrom:'20000202000000+0200' onError:[]

     AbsoluteTime readGeneralizedFrom:'19950220131106' onError:[]   
     AbsoluteTime readGeneralizedFrom:'199502201311' onError:[]    
     AbsoluteTime readGeneralizedFrom:'19950220131106.100' onError:[]    
     AbsoluteTime readGeneralizedFrom:'19950232131106.100' onError:'wrong'    
     AbsoluteTime readGeneralizedFrom:'19950fo2131106.100' onError:'wrong'    
     AbsoluteTime readGeneralizedFrom:'foo' onError:'wrong'                     
    "

    "Modified: / 8.10.1996 / 19:25:59 / cg"
    "Modified: / 13.7.1999 / 12:31:14 / stefan"
!

readIso8601FormatFrom:aStringOrStream
    "return a new AbsoluteTime, reading an iso8601 UTC representation from aStream.
     Missing month/day values are replaced with 1; i.e. 1999T24:00
     is the same as 1999-01-01T24:00:00.
     Missing minute, second and ms values are replaced with 0;
     i.e. 1999T12 is the same as 1999-01-01T12:00:00.000.
     Of course, a 24 hour clock is used.
     On error, raise an exception.
     Please use this format for all external representations - its the standard."

    ^ self
        readIso8601FormatFrom:aStringOrStream yearAlreadyRead:nil

    "
     AbsoluteTime readIso8601FormatFrom:'1995-02-20T13:11:06'    
     AbsoluteTime readIso8601FormatFrom:'1995-02T13:11:06'     
     AbsoluteTime readIso8601FormatFrom:'1995T13:11:06'        
     AbsoluteTime readIso8601FormatFrom:'1995T13:11'           
     AbsoluteTime readIso8601FormatFrom:'1995T13'              
     AbsoluteTime readIso8601FormatFrom:'1995'              

     AbsoluteTime readIso8601FormatFrom:'1995-02-20 13:11:06'    
     AbsoluteTime readIso8601FormatFrom:'1995-02-20 13:11'    
     AbsoluteTime readIso8601FormatFrom:'1995-02-20 13'    

   24 is allowed with ISO, and is 00:00 of the next day:
     AbsoluteTime readIso8601FormatFrom:'1995-02-20 24:00:00'    

    "
!

readIso8601FormatFrom:aStringOrStream yearAlreadyRead:yearOrNil
    "common helper for read methods.
     Return a new AbsoluteTime, reading an iso8601 UTC representation from aStream.
     Missing month/day values are replaced with 1; i.e. 1999T24:00
     is the same as 1999-01-01T24:00:00.
     Missing minute, second and ms values are replaced with 0;
     i.e. 1999T12 is the same as 1999-01-01T12:00:00.000.
     Of course, a 24 hour clock is used.
     On error, raise an exception.
     Please use this format for all external representations - its the standard."

    |str day month year hour min sec millis fraction|

    str := aStringOrStream readStream.

    month := day := 1.
    hour := min := sec := millis := 0.

    yearOrNil notNil ifTrue:[
        year := yearOrNil
    ] ifFalse:[
        year := Integer readFrom:str.
    ].

    str skipSeparators.
    str peek == $- ifTrue:[
        str next.
        "/ month follows.
        month := Integer readFrom:str.
        (month between:1 and:12) ifFalse:[ ConversionError raiseErrorString:'bad month' ].

        str skipSeparators.
        str peek == $- ifTrue:[
            str next.
            "/ day follows.
            day := Integer readFrom:str.
            (day between:1 and:31) ifFalse:[ ConversionError raiseErrorString:'bad day' ].
        ].
    ].

    str skipSeparators.
    str atEnd ifFalse:[
        "time follows"

        str peek == $T ifTrue:[
            "we treat the T as optional here"
            str next.
            str skipSeparators.
        ].
        hour := Integer readFrom:str.
        (hour between:0 and:24) ifFalse:[ ConversionError raiseErrorString:'bad hour' ].
        str skipSeparators.
        str peek == $: ifTrue:[
            str next.
            "/ minutes follow.
            min := Integer readFrom:str.
            (min between:0 and:59) ifFalse:[ ConversionError raiseErrorString:'bad minute' ].
            str skipSeparators.
            str peek == $: ifTrue:[
                str next.
                "/ seconds follow.
                sec := Integer readFrom:str.
                (sec between:0 and:59) ifFalse:[ ConversionError raiseErrorString:'bad seconds' ].
                str skipSeparators.
                str peek == $. ifTrue:[
                    str next.
                    "/ millis follow.
                    fraction := Number readMantissaFrom:str radix:10.
                    millis := 1000 * fraction rounded.  "/ mhmh - should it be truncated ?
                ]
            ].
        ].
    ].

    "special check - only 24:00:00 is allowed;
     every time after that must wrap"
    hour == 24 ifTrue:[
        (min ~~ 0 or:[sec ~~ 0 or:[millis ~~ 0]]) ifTrue:[ Error raiseErrorString:'bad hour' ].
    ].
    ^ self 
        year:year month:month day:day 
        hour:hour minute:min second:sec millisecond:millis.

    "
     AbsoluteTime readIso8601FormatFrom:'1995-02-20T13:11:06'    
     AbsoluteTime readIso8601FormatFrom:'1995-02T13:11:06'     
     AbsoluteTime readIso8601FormatFrom:'1995T13:11:06'        
     AbsoluteTime readIso8601FormatFrom:'1995T13:11'           
     AbsoluteTime readIso8601FormatFrom:'1995T13'              
     AbsoluteTime readIso8601FormatFrom:'1995'              

     AbsoluteTime readIso8601FormatFrom:'1995-02-20 13:11:06'    
     AbsoluteTime readIso8601FormatFrom:'1995-02-20 13:11'    
     AbsoluteTime readIso8601FormatFrom:'1995-02-20 13'    

   24 is allowed with ISO, and is 00:00 of the next day:
     AbsoluteTime readIso8601FormatFrom:'1995-02-20 24:00:00'    
    "
!

secondsSince1970:sec
    "set time from elapsed seconds since 1-1-1970, 0:0:0.
     This is the format used in the UNIX world"

    ^ self year:1970 month:1 day:1 hour:(sec // 3600) minute:0 second:(sec \\ 3600).

"/    ^ self year:1970 month:1 day:1 hour:0 minute:0 second:sec.

    "
     AbsoluteTime secondsSince1970:0      
     AbsoluteTime secondsSince1970:3600
     AbsoluteTime secondsSince1970:3600*24
    "

    "Created: / 21.10.1996 / 17:48:30 / stefan"
    "Modified: / 13.7.1999 / 12:31:22 / stefan"
!

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

    ^ self year:y month:m day:d hour:h minute:min second:s millisecond:0

    "
     AbsoluteTime year:1970 month:1 day:1 hour:1 minute:0 second:0 
     AbsoluteTime year:1991 month:1 day:2 hour:12 minute:30 second:0 
     AbsoluteTime year:1991 month:1 day:2 hour:12 minute:30 second:0 millisecond:100
     AbsoluteTime year:2000 month:1 day:1 hour:1 minutes:0 second:0 
    "

    "Modified: / 1.7.1996 / 15:22:07 / cg"
    "Created: / 13.7.1999 / 12:06:39 / stefan"
    "Modified: / 13.7.1999 / 12:27:47 / stefan"
!

year:y month:m day:d hour:h minute:min second:s millisecond: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 year:1970 month:1 day:1 hour:1 minute:0 seconds:0 
     AbsoluteTime year:1991 month:1 day:2 hour:12 minute:30 second:0 
     AbsoluteTime year:1991 month:1 day:2 hour:12 minute:30 second:0 millisecond:100
     AbsoluteTime year:2000 month:1 day:1 hour:1 minute:0 second:0 
    "

    "Modified: / 1.7.1996 / 15:22:07 / cg"
    "Created: / 13.7.1999 / 12:28:44 / stefan"
    "Modified: / 13.7.1999 / 12:37:57 / stefan"
! !

!AbsoluteTime methodsFor:'accessing'!

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

    |v d|

    v := OperatingSystem computeTimeAndDateFrom:osTime.
    d := v at:3.
"/    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
     WARNING: different from ANSIs dayOfWeek (which returns 1 for sunday, ... 7 for saturday).  
     WARNING: does not care for pre-julian dates 
        (i.e. do not use this for dates before 1752)"

    ^ (OperatingSystem computeTimeAndDateFrom:osTime) 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."

    ^ (OperatingSystem computeTimeAndDateFrom:osTime) 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)"

    |v hr|

    v := OperatingSystem computeTimeAndDateFrom:osTime.
    hr := v at:4.

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

    |v m|

    v := OperatingSystem computeTimeAndDateFrom:osTime.
    m := v at:9.
"/    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)"

    |v m|

    v := OperatingSystem computeTimeAndDateFrom:osTime.
    m := v at:5.
"/    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."

    |v m|

    v := OperatingSystem computeTimeAndDateFrom:osTime.
    m := v at:2.
"/    OperatingSystem computeDatePartsOf:osTime for:[ :year :month :day |
"/        m := month
"/    ].
    ^ m

    "
     AbsoluteTime now month
    "

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

osTime:aTime
    "set the internal representation of the time"

    osTime := aTime.
!

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

    |v s|

    v := OperatingSystem computeTimeAndDateFrom:osTime.
    s := v at:6.
"/    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 before 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."

    |v y|

    v := OperatingSystem computeTimeAndDateFrom:osTime.
    y := v at:1.
"/    OperatingSystem computeDatePartsOf:osTime for:[:year :month :day |
"/        y := year
"/    ].
    ^ y

    "
     AbsoluteTime now year
    "

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

!AbsoluteTime methodsFor:'arithmetic'!

millisecondDeltaFrom:anAbsoluteTime
    "return the delta in milliseconds between 2 absolute times.
     The argument is supposed to be AFTER the receiver"

    ^ self getMilliseconds - (anAbsoluteTime getMilliseconds)

    "
     |t1 t2|

     t1 := AbsoluteTime now.
     Delay waitForSeconds:0.5.
     t2 := AbsoluteTime now.
     t2 millisecondDeltaFrom:t1   
    "

    "Modified: / 5.6.1998 / 04:21:33 / cg"
! !

!AbsoluteTime methodsFor:'comparing'!

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

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

literalArrayEncoding
    "encode myself as an array, from which a copy of the receiver
     can be reconstructed with #decodeAsLiteralArray.
     The encoding is: 
        (#AbsoluteTime YYYYMMDDhhmmss.iii)
    "

    |s|

    s := '' writeStream.
    self printGeneralizedOn:s isLocal:true.

    ^ Array
        with:self class name asSymbol
        with:s contents

    "
      AbsoluteTime now literalArrayEncoding 
      AbsoluteTime decodeFromLiteralArray:AbsoluteTime now literalArrayEncoding
    "



!

utcSecondsSince1901
    "return the number of seconds elapsed since Jan, 1st 1901"

    |daysBetween1901and1970 secondsPerDay|

    daysBetween1901and1970 := (Date day:1 month:1 year:1970) subtractDate:(Date day:1 month:1 year:1901).
    secondsPerDay := 24 * 60 * 60.
    ^ self utcSecondsSince1970 " since 1.1.1970 "
      + (daysBetween1901and1970 * secondsPerDay).  

    "                                                 
     AbsoluteTime now utcSecondsSince1901 
    "
! !

!AbsoluteTime methodsFor:'encoding'!

encodeOn:anEncoder with:aParameter
    "encoder visitor support"

    anEncoder encodeAbsoluteTime:self with:aParameter
! !

!AbsoluteTime methodsFor:'printing & storing'!

addPrintBindingsTo:dict
    "private print support"

    self asDate addPrintBindingsTo:dict.

    self year == Date today year ifTrue:[
        dict at:#yearOrTime put:(self asTime printStringFormat:'%h:%m').
    ].

    super addPrintBindingsTo:dict.

"/    |d m y s|
"/
"/    OperatingSystem computeDatePartsOf:osTime for:[
"/        :year :month :day | d := day. m := month. y := year.
"/    ].
"/    dict at:#day put:(d printString leftPaddedTo:2 with:$0).
"/    dict at:#dayInWeek put:(self dayInWeek).
"/    dict at:#month put:(s := m printString leftPaddedTo:2 with:$0).
"/    dict at:#mon put:s.   "/ for backward compatibility only
"/    dict at:#year put:(y printString leftPaddedTo:4 with:$0).
"/
"/    dict at:#Day put:d printString.
"/    dict at:#Month put:(s := m printString).
"/    dict at:#Mon put:s.   "/ for backward compatibility only

    "
     AbsoluteTime now printOn:Transcript format:'%(day).%(ShortMonthName)'. Transcript cr.      
     AbsoluteTime now printOn:Transcript format:'%(day):%(month)'. Transcript cr.      
     AbsoluteTime now printOn:Transcript format:'%(dayInWeek)'. Transcript cr.      
     AbsoluteTime now printOn:Transcript format:'%(Day)-%(month)-%(year) %h:%m:%s.%i'. Transcript cr.      
     AbsoluteTime now printOn:Transcript. Transcript cr
    "
!

printGeneralizedOn:aStream 
    "append a representation of the receiver to aStream in a general format,
     top-down, without separtors: 'yyyymmddHHMMSS.mmm+0100'
     This format is used for the ASN.1 GeneralizedTime as defined in X.208 Sec. 33,
     so read this before changing the output format."

    ^ self printGeneralizedOn:aStream isLocal:false.
!

printGeneralizedOn:aStream isLocal:isLocal
    "append a representation of the receiver to aStream in a general format,
     top-down, without separtors: 'yyyymmddHHMMSS.mmm+0100'
     This format is used for the ASN.1 GeneralizedTime as defined in X.208 Sec. 33,
     so read this before changing the output format.

     If isLocal is true, represent as local time, otherwise add UTC time offset."

    |t off|

    t := OperatingSystem computeTimeAndDateFrom:osTime.

    (t at:1) printOn:aStream leftPaddedTo:4 with:$0.
    (t at:2) printOn:aStream leftPaddedTo:2 with:$0.
    (t at:3) printOn:aStream leftPaddedTo:2 with:$0.
    (t at:4) printOn:aStream leftPaddedTo:2 with:$0. 
    (t at:5) printOn:aStream leftPaddedTo:2 with:$0.
    (t at:6) printOn:aStream leftPaddedTo:2 with:$0.
    aStream nextPut:$..
    (t at:9) printOn:aStream leftPaddedTo:3 with:$0.

    isLocal ifFalse:[
        "/ this should be printed as non-local-time

        off := t at:7.
        off == 0 ifTrue:[
            aStream nextPut:$Z.
        ] ifFalse:[ |min|
            off < 0 ifTrue:[
                aStream nextPut:$+.
                off := off negated.
            ] ifFalse:[
                aStream nextPut:$-.
            ].
            min := off // 60.
            min // 60 printOn:aStream leftPaddedTo:2 with:$0.
            min \\ 60 printOn:aStream leftPaddedTo:2 with:$0.
        ].
    ].


    "
     AbsoluteTime now printGeneralizedOn:Transcript. Transcript cr. 
     (AbsoluteTime fromSeconds:0) printGeneralizedOn:Transcript. Transcript cr.
     Time now printOn:Transcript. Transcript cr.           
     Date today printOn:Transcript. Transcript cr.        

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

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

    "Modified: / 1.7.1996 / 15:20:59 / cg"
    "Modified: / 17.1.2000 / 15:53:02 / stefan"
!

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

    "/ now, use ISO format...
    self printOn:aStream format:'%(year)-%(mon)-%(day) %h:%m:%s.%i'  
"/    self printOn:aStream format:'%(Day)-%(mon)-%(year) %h:%m:%s.%i'  
"/    self printOn:aStream format:'%(mon)/%(Day)/%(year) %h:%m:%s.%i'  

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

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

utcSecondsSince1970
    "return the UTC seconds since 1970"

    |localTimeSeconds|

    OperatingSystem isUNIXlike ifFalse:[
        self error:'unimplemented'.
    ].
    localTimeSeconds := self getSeconds.
    ^ localTimeSeconds - self utcOffset

    "
     AbsoluteTime now utcSecondsSince1970
    "
! !

!AbsoluteTime class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Timestamp.st,v 1.77 2003-06-03 10:36:42 cg Exp $'
! !