Timestamp.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 15 Jun 2009 20:55:05 +0100
branchjv
changeset 17711 39faaaf888b4
parent 11177 f5faa6cb49ed
child 17728 bbc5fa73dfab
permissions -rw-r--r--
Added branch jv

"
 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:#Timestamp
	instanceVariableNames:'osTime'
	classVariableNames:''
	poolDictionaries:''
	category:'Magnitude-Time'
!

!Timestamp 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 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 returned 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 timestamps on files 
     (such as last-access-time or last-modification-time) can be handled transparently - 
     especially when performing comparisons).

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

    The implementation of this class is not the same as in ST-80 
    (which represents the time as seconds from Jan 1., 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 Timestamp can.

    Notice: this class was once called AbsoluteTime. Einstein told us in 1905, that talking
    about a absolute time is not a good idea (at least in our universe). So the class
    has been renamed to Timestamp which makes us more compatible to other ST dialects (e.g. VW)
    AbsoluteTime is still kept as an alias for backward compatibility.

    [author:]
        Claus Gittinger

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

!Timestamp class methodsFor:'initialization'!

initialize

    AbsoluteTime := self.       "backward compatibility"
! !

!Timestamp 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 `Timestamp 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)

    "
     Timestamp UTCYear:1970 month:1 day:1 hour:1 minute:0 second:0 millisecond:0
     Timestamp UTCYear:1991 month:1 day:2 hour:12 minute:30 second:0 millisecond:0
     Timestamp UTCYear:1991 month:1 day:2 hour:12 minute:30 second:0 millisecond:100
     Timestamp UTCYear:1999 month:7 day:1 hour:1 minute:0 second:0 millisecond:0
     Timestamp 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"
!

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

    "
     Timestamp day:2 month:1 year:1991 hour:12 minute:30 second:0 
     Timestamp 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

    "
     Timestamp day:1 month:1 year:1970 hour:1 minute:0 second:0 
     Timestamp day:2 month:1 year:1991 hour:12 minute:30 second:0 
     Timestamp 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 Timestamp literalArray.

     anArray may be:
        #(Timestamp '200004182000.123')

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

        #(Timestamp #osTime: 12345678)     
    "

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

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

    "
     Timestamp
        decodeFromLiteralArray:#(Timestamp '20050323175226.014')      
    "
!

fromDate:aDate andTime:aTime
    "return an instance of the receiver, initialized from a time and a date
     object.
     See also `Timestamp 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 

    "
     Timestamp fromDate:(Date today) andTime:(Time now)  
     Timestamp fromDate:(Date today plusDays:1) andTime:(Time now) 
     Timestamp 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 Timestamp, given the year and the day-in-year (starting at 1).
     Date protocol compatibility"

    ^ (Date newDay:dayInYear year:year) asTimestamp

    "
     Timestamp newDay:183 year:1996
    "

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

readFrom:aStringOrStream onError:exceptionBlock
    "return a new Timestamp, 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"

    |stream newTime|

    stream := aStringOrStream readStream.

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

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

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

readGeneralizedFrom:aStringOrStream 
    "return a new Timestamp, 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 either
        yyyymmddHHMMSS.iii+uuuu, which is the ASN1 GeneralizedTime format.
     or:
        yyyy-mm-dd HH:MM:SS.iii +uuuu.
    "
    ^ self 
        readGeneralizedFrom:aStringOrStream 
        onError:[self conversionErrorSignal 
                    raiseErrorString:'Timestamp format error' ].

    "Created: / 22-08-2006 / 16:05:55 / cg"
!

readGeneralizedFrom:aStringOrStream onError:exceptionBlock
    "return a new Timestamp, 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 either
        yyyymmddHHMMSS.iii+uuuu, which is the ASN1 GeneralizedTime format.
     or:
        yyyy-mm-dd HH:MM:SS.iii +uuuu.
    "

    |newTime|

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

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

        year := Integer readFrom:(str next:4).
        str peek == $- ifTrue:[ str next].
        month := Integer readFrom:(str next:2).
        (month between:1 and:12) ifFalse:[^ exceptionBlock value].
        str peek == $- ifTrue:[ str next].
        day := Integer readFrom:(str next:2).
        (day between:1 and:31) ifFalse:[^ exceptionBlock value].

        str skipSeparators.
        hour:= Integer readFrom:(str next:2).
        (hour between:0 and:24) ifFalse:[^ exceptionBlock value].
        str peek == $: ifTrue:[ str next].
        min:= Integer readFrom:(str next:2).
        (min between:0 and:59) ifFalse:[^ exceptionBlock value].
        str atEnd ifFalse:[
            str peek == $: ifTrue:[ str next].
            sec := Integer readFrom:(str next:2).
            (sec between:0 and:59) ifFalse:[^ exceptionBlock value].
            str atEnd ifFalse:[
                str peek == $. ifTrue:[
                    str next.
                    millis := Integer readFrom:str.
                ].
                str skipSeparators.
            ].
        ].

        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:[
                    "the timezone is ahead of UTC or EAST from Greenwich: subtract hours and minutes"
                    hour := hour - tzh.
                    min := min - tzmin.
                ] ifFalse:[
                    c ~~ $- ifTrue:[
                        ^ exceptionBlock value.
                    ].
                    "the timezone is behind of UTC or WEST from Greenwich: add 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.
     Timestamp now printGeneralizedOn:s.
     Timestamp readGeneralizedFrom:s contents onError:[]

 Daylight saving time:

     Timestamp readGeneralizedFrom:'20000718120000Z' onError:[]
     Timestamp readGeneralizedFrom:'20000718120000+0200' onError:[]
     Timestamp readGeneralizedFrom:'20000718120000+0300' onError:[]

 No daylight saving time:

     Timestamp readGeneralizedFrom:'20000202120000Z' onError:[]
     Timestamp readGeneralizedFrom:'20000202120000+0100' onError:[]
     Timestamp readGeneralizedFrom:'20000202120000+0200' onError:[]

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

     Timestamp readGeneralizedFrom:'2000-02-02 12:00:00' onError:[]   
     Timestamp readGeneralizedFrom:'2000-02-02 12:00:00.100' onError:[]
     Timestamp readGeneralizedFrom:'2000-02-02 12:00:00.100 +0100' onError:[] 
     Timestamp readGeneralizedFrom:'2000-02-02 12:00:00 -0100' onError:[]
     Timestamp readGeneralizedFrom:'2000-02-02 12:00:00 +0000' onError:[] 
    "

    "Modified: / 13-07-1999 / 12:31:14 / stefan"
    "Modified: / 22-08-2006 / 12:30:11 / cg"
!

readIso8601FormatFrom:aStringOrStream
    "return a new Timestamp, 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

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

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

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

    "
!

readIso8601FormatFrom:aStringOrStream onError:exceptionValue
    "return a new Timestamp, 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 
        onError:exceptionValue
!

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

    |divMod|

    divMod := sec divMod:3600.
    ^ self year:1970 month:1 day:1 hour:(divMod at:1) minute:0 second:(divMod at:2) millisecond:0.

    "
     Timestamp secondsSince1970:0      
     Timestamp secondsSince1970:3600
     Timestamp 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 `Timestamp now' and other protocol inherited
     from my superclass."

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

    "
     Timestamp year:1970 month:1 day:1 hour:1 minute:0 second:0 
     Timestamp year:1991 month:1 day:2 hour:12 minute:30 second:0 
     Timestamp year:1991 month:1 day:2 hour:12 minute:30 second:0 millisecond:100
     Timestamp 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 `Timestamp 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)

    "
     Timestamp year:1970 month:1 day:1 hour:0 minute:0 second:0 
     Timestamp year:1991 month:1 day:2 hour:12 minute:30 second:0 
     Timestamp year:1991 month:1 day:2 hour:12 minute:30 second:0 millisecond:100
     Timestamp 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"
! !

!Timestamp class methodsFor:'private'!

basicReadFrom:aStream
    "return a new Timestamp, 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"

    |firstNumber secondNumber day month year hour min sec millis usFormat possibeMonthName|

    firstNumber := Integer readFrom:aStream onError:[ConversionError raiseErrorString:' - integer expected'].
    firstNumber > 31 ifTrue:[
        "/ assume iso8601 format;
        ^ self readIso8601FormatFrom:aStream yearAlreadyRead:firstNumber.
    ].
    aStream skipSeparators.

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

    [aStream peek isLetterOrDigit] whileFalse:[aStream next].
    aStream peek isDigit ifTrue:[
        secondNumber := Integer readFrom:aStream onError:-1.

        usFormat ifTrue:[
            month := firstNumber.
            day := secondNumber.
        ] ifFalse:[
            month := secondNumber.
            day := firstNumber.
        ].

    ] ifFalse:[
        possibeMonthName := aStream throughAnyForWhich:[:ch | ch isLetter].
        month := Date indexOfMonth:possibeMonthName asLowercase.
        day := firstNumber.
    ].

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

    [aStream peek isDigit] whileFalse:[aStream next].
    year := Integer readFrom:aStream onError:[ ConversionError raiseErrorString:' - bad year' ].

    aStream atEnd ifTrue:[
        hour := min := sec := millis := 0.
    ] ifFalse:[
        [aStream peek isDigit] whileFalse:[aStream next].
        hour := Integer readFrom:aStream onError:-1.
        (hour between:0 and:24) ifFalse:[ ConversionError raiseErrorString:' - bad hour' ].

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

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

            aStream peek = $. ifTrue:[
                aStream next.
                millis := Integer readFrom:aStream onError:0.
                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.

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

readIso8601FormatFrom:aStringOrStream yearAlreadyRead:yearOrNil
    "common helper for read methods.
     Return a new Timestamp, 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 onError:nil.
        year isNil ifTrue:[ ConversionError raiseErrorString:' - bad year' ]
    ].

    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 onError:-1.
        (hour between:0 and:24) ifFalse:[ ConversionError raiseErrorString:' - bad hour' ].
        str skipSeparators.
        str peek == $: ifTrue:[
            str next.
            "/ minutes follow.
            min := Integer readFrom:str onError:-1.
            (min between:0 and:59) ifFalse:[ ConversionError raiseErrorString:' - bad minute' ].
            str skipSeparators.
            str peek == $: ifTrue:[
                str next.
                "/ seconds follow.
                sec := Integer readFrom:str onError:-1.
                (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:[ ConversionError raiseErrorString:' - bad hour' ].
    ].
    ^ self 
        year:year month:month day:day 
        hour:hour minute:min second:sec millisecond:millis.

    "
     Timestamp readIso8601FormatFrom:'1995-02-20T13:11:06.123'    
     Timestamp readIso8601FormatFrom:'1995-02-20T13:11:06'    
     Timestamp readIso8601FormatFrom:'1995-02T13:11:06'     
     Timestamp readIso8601FormatFrom:'1995T13:11:06'        
     Timestamp readIso8601FormatFrom:'1995T13:11'           
     Timestamp readIso8601FormatFrom:'1995T13'              
     Timestamp readIso8601FormatFrom:'1995'              

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

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

readIso8601FormatFrom:aStringOrStream yearAlreadyRead:yearOrNil onError:exceptionValue
    "common helper for read methods.
     Return a new Timestamp, 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."

    |retVal|

    ConversionError handle:[:ex |
        retVal := exceptionValue value
    ] do:[
        retVal := self readIso8601FormatFrom:aStringOrStream yearAlreadyRead:yearOrNil
    ].
    ^ retVal
! !

!Timestamp methodsFor:'accessing'!

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

    ^ (OperatingSystem computeTimeAndDateFrom:osTime) day.

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

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

    "
     Timestamp now dayInYear 
     Timestamp 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)"

    ^ (OperatingSystem computeTimeAndDateFrom:osTime) hours

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

    ^ (OperatingSystem computeTimeAndDateFrom:osTime) milliseconds

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

    ^ (OperatingSystem computeTimeAndDateFrom:osTime) minutes

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

    ^ (OperatingSystem computeTimeAndDateFrom:osTime) month

    "
     Timestamp now month
    "

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

osTime
    "get the internal representation of the time.
     Warning: do not depend on the value (unix vs. win32 - differences)"

    ^ osTime
!

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

    ^ (OperatingSystem computeTimeAndDateFrom:osTime) seconds

    "
     Timestamp now seconds 
    "

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

timeInfo
    ^ (OperatingSystem computeTimeAndDateFrom:osTime)
!

utcOffset
    "return the difference between UTC (Greenwich Mean Time) and the local time in seconds.
     If daylight saving time applies to ourself, take that into account.

     Add utcOffset to convert from local time to UTC time.
     Subtract utcOffset to convert from UTC time to local time.

     If utcOffset is negative, the local timezone is east of Greenwich.
     If utcOffset is positive, the local timezone is west of Greenwich."

    ^ (OperatingSystem computeTimeAndDateFrom:osTime) utcOffset

    "
     Timestamp now utcOffset 
     (Timestamp 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."

    ^ (OperatingSystem computeTimeAndDateFrom:osTime) year

    "
     Timestamp now year
    "

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

!Timestamp methodsFor:'arithmetic'!

deltaFrom:aTimestamp
    "return the delta as a timeDuration between 2 timeStamps.
     The argument is supposed to be BEFORE the receiver"

    ^ TimeDuration fromMilliseconds:(self getMilliseconds - (aTimestamp getMilliseconds))

    "
     |t1 t2|

     t1 := Timestamp now.
     Delay waitForSeconds:0.5.
     t2 := Timestamp now.
     t2 deltaFrom:t1   
    "

    "Created: / 04-10-2007 / 13:34:28 / cg"
!

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

    ^ self getMilliseconds - (aTimestamp getMilliseconds)

    "
     |t1 t2|

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

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

secondDeltaFrom:aTimestamp
    "return the delta in seconds between 2 absolute times.
     The argument is supposed to be BEFORE the receiver"

    ^ self getSeconds - (aTimestamp getSeconds)

    "
     |t1 t2|

     t1 := Timestamp now.
     Delay waitForSeconds:5.
     t2 := Timestamp now.
     t2 secondDeltaFrom:t1   
    "

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

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

!Timestamp methodsFor:'converting'!

asAbsoluteTime
    "deprecated, use #asTimestamp"

    <resource:#obsolete>

    self obsoleteMethodWarning:'use #asTimestamp'.
    ^ self
!

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

    ^ Date fromOSTime:osTime 

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

asLocalTimestamp
    "convert an utc timestamp to local time "

    ^ self - self utcOffset

    "
     Timestamp now asUtcTimestamp
     Timestamp now asUtcTimestamp asLocalTimestamp
    "
!

asMilliseconds
    "return the number of milliSeconds 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 milliSeconds or get time deltas, though."

    ^ self getMilliseconds
!

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

    "                                                 
     Timestamp now asSeconds
     Timestamp fromSeconds:(Timestamp 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

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

asTimestamp
    "return an Timestamp object from the receiver - thats the receiver."

    ^ self 
!

asUtcTimestamp
    "convert a local time timestamp to UTC"

    ^ self + self utcOffset

    "
     Timestamp now asUtcTimestamp
    "
!

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

    |s|

    s := WriteStream on:(String new:18).
    self printGeneralizedOn:s isLocal:true.

    ^ Array
        with:self class name
        with:s contents

    "
      Timestamp now literalArrayEncoding
        decodeAsLiteralArray
    "
!

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

"   
    secondsBetween1901and1970 := 
        ((Date day:1 month:1 year:1970) subtractDate:(Date day:1 month:1 year:1901))
        *  (24 * 60 * 60)
"

    ^ self utcSecondsSince1970 + 2177452800.  

    "                                                 
     Timestamp now utcSecondsSince1901 
    "
! !

!Timestamp methodsFor:'printing & storing'!

addPrintBindingsTo:dict language:languageOrNil
    "private print support: add bindings for printing to aDictionary
     languageOrNil can only be #en or nil for the current language."

    self asDate addPrintBindingsTo:dict language:languageOrNil.

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

    super addPrintBindingsTo:dict language:languageOrNil.
!

printGeneralizedOn:aStream 
    "append a representation of the receiver to aStream in a general format,
     top-down, without separators: '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 separators: '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 year    printOn:aStream leftPaddedTo:4 with:$0.
    t month   printOn:aStream leftPaddedTo:2 with:$0.
    t day     printOn:aStream leftPaddedTo:2 with:$0.
    t hours   printOn:aStream leftPaddedTo:2 with:$0. 
    t minutes printOn:aStream leftPaddedTo:2 with:$0.
    t seconds printOn:aStream leftPaddedTo:2 with:$0.
    aStream nextPut:$..
    t milliseconds printOn:aStream leftPaddedTo:3 with:$0.

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

        off := t utcOffset.
        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.
        ].
    ].

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

     Time now asTimestamp printGeneralizedOn:Transcript. Transcript cr.           
     Timestamp now printGeneralizedOn:Transcript. Transcript cr. 

     Date today asTimestamp 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"
!

printIso8601FormatOn:aStream
    "append the iso8601 UTC representation of the receiver to aStream.
     This format looks like:
        1999-01-01T24:00:00
     or, for zero hr:min:sec, 
        1999-01-01
     Of course, a 24 hour clock is used."

    |format|

    format := '%(year)-%(month)-%(day)T%h:%m:%s.%i'.
    self milliseconds = 0 ifTrue:[
        format := '%(year)-%(month)-%(day)T%h:%m:%s'.
        self seconds = 0 ifTrue:[
            format := '%(year)-%(month)-%(day)T%h:%m'.
            ((self hours = 0) and:[self minutes = 0]) ifTrue:[
                format := '%(year)-%(month)-%(day)'.
            ]
        ]
    ].
    self printOn:aStream format:format 

    "
     Timestamp now printIso8601FormatOn:Transcript   
     Timestamp readIso8601FormatFrom:(Timestamp now printStringIso8601Format).
    "
!

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'  

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

     Time now asTimestamp printOn:Transcript. Transcript cr.           
     Timestamp now printOn:Transcript. Transcript cr. 

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

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

printRFC1123FormatOn:aStream
    "append the RFC1123 representation of the receiver to aStream.
     This format is used in HTTP requests and looks like:
        'Fri, 04 Jul 2003 15:56:11 GMT'
     (always GMT and all names in english)"

"/       HTTP-date      = rfc1123-date | rfc850-date | asctime-date
"/
"/       rfc1123-date   = wkday "," SP date1 SP time SP "GMT"
"/       rfc850-date    = weekday "," SP date2 SP time SP "GMT"
"/       asctime-date   = wkday SP date3 SP time SP 4DIGIT
"/
"/       date1          = 2DIGIT SP month SP 4DIGIT
"/                        ; day month year (e.g., 02 Jun 1982)
"/       date2          = 2DIGIT "-" month "-" 2DIGIT
"/                        ; day-month-year (e.g., 02-Jun-82)
"/       date3          = month SP ( 2DIGIT | ( SP 1DIGIT ))
"/                        ; month day (e.g., Jun  2)
"/
"/       time           = 2DIGIT ":" 2DIGIT ":" 2DIGIT
"/                        ; 00:00:00 - 23:59:59
"/
"/       wkday          = "Mon" | "Tue" | "Wed"
"/                      | "Thu" | "Fri" | "Sat" | "Sun"
"/
"/       weekday        = "Monday" | "Tuesday" | "Wednesday"
"/                      | "Thursday" | "Friday" | "Saturday" | "Sunday"
"/
"/       month          = "Jan" | "Feb" | "Mar" | "Apr"
"/                      | "May" | "Jun" | "Jul" | "Aug"
"/                      | "Sep" | "Oct" | "Nov" | "Dec"

    |meUTC timeInfo|

    meUTC := self class fromSeconds:((self asSeconds) + (self utcOffset)).
    timeInfo := meUTC timeInfo.

    aStream nextPutAll:(#('Mon' 'Tue' 'Wed' 'Thu' 'Fri' 'Sat' 'Sun') at:timeInfo dayInWeek);
            nextPutAll:', '.
    timeInfo day printOn:aStream leftPaddedTo:2 with:$0.
    aStream space.
    aStream nextPutAll:(#('Jan' 'Feb' 'Mar' 'Apr' 'May' 'Jun' 'Jul' 'Aug' 'Sep' 'Oct' 'Nov' 'Dec') at:timeInfo month).

"/ The following line is wrong, because the names are printed in the current locale!!
"/    timeInfo printOn:aStream format:'%(ShortDayName), %(day) %(ShortMonthName) %y %h:%m:%s GMT'. 

"/ the following is too slow for heavy use    
"/    timeInfo printOn:aStream format:' %y %h:%m:%s GMT'. 

    aStream nextPut:Character space.
    timeInfo year printOn:aStream.
    aStream nextPut:Character space.
    timeInfo hours printOn:aStream leftPaddedTo:2 with:$0.
    aStream nextPut:$:.
    timeInfo minutes printOn:aStream leftPaddedTo:2 with:$0.
    aStream nextPut:$:.
    timeInfo seconds printOn:aStream leftPaddedTo:2 with:$0.
    aStream nextPutAll:' GMT'.

    "
     Timestamp now printRFC1123FormatOn:Transcript   
    "
!

printStringIso8601Format
    "return the Iso8601 representation of the receiver.
     This format looks like:
        1999-01-01T24:00:00
     or, for zero hr:min:sec, 
        1999-01-01
     Of course, a 24 hour clock is used."

    ^ String streamContents:[:s | self printIso8601FormatOn:s]

    "
     Timestamp now printStringIso8601Format
    "
!

printStringRFC1123Format
    "return the RFC1123 representation of the receiver.
     This format is used in HTTP requests and looks like:
        'Fri, 04 Jul 2003 15:56:11 GMT'
     (always GMT)"

    ^ String streamContents:[:s | self printRFC1123FormatOn:s]

    "
     Timestamp now printStringRFC1123Format
    "
!

storeOn:aStream
    "store the receiver in a format suitable for reconstruction of the
     receiver via readFrom:
     Use a OS/architecture independent format"

    aStream nextPut:$(; 
            nextPutAll:self class name; 
            nextPutAll:' readIso8601FormatFrom:'''.
    self printIso8601FormatOn:aStream.
    aStream nextPutAll:''')'.

    "
     Timestamp now storeString 

     Object readFrom:(Timestamp now storeString) readStream
     Timestamp readFrom:(Timestamp now storeString) readStream
    "
! !

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

    ^ self getSeconds

    "
     Timestamp now utcSecondsSince1970
    "
! !

!Timestamp methodsFor:'visiting'!

acceptVisitor:aVisitor with:aParameter

    ^ aVisitor visitTimestamp:self with:aParameter
! !

!Timestamp class methodsFor:'documentation'!

version
    ^ '$Id: Timestamp.st 10447 2009-06-14 13:09:55Z vranyj1 $'
! !

Timestamp initialize!