Timestamp.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Thu, 19 Jan 2012 11:46:00 +0000
branchjv
changeset 17911 a99f15c5efa5
parent 17910 8d796ca8bd1d
child 17976 50c2416f962a
permissions -rw-r--r--
Updated with /trunk

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

Object subclass:#TimestampBuilderAbstract
	instanceVariableNames:'year month day hour minute second millisecond isUtcTime'
	classVariableNames:''
	poolDictionaries:''
	privateIn:Timestamp
!

Timestamp::TimestampBuilderAbstract subclass:#TimestampISO8601Builder
	instanceVariableNames:'stream'
	classVariableNames:''
	poolDictionaries:''
	privateIn:Timestamp
!

!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. When printing an accessing values like #hour, the timestamp will be
    interpreted in the local timezone.

    (The internal representation, osTime, will typically start with 1970-01-01 0:00, 
     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:]
        UtcTimestamp Time Date
        Delay ProcessorScheduler
"
! !

!Timestamp class methodsFor:'initialization'!

initialize

    AbsoluteTime := self.       "backward compatibility"
    DateAndTime isNil ifTrue:[
        DateAndTime := self
    ].

    "Modified: / 20-08-2011 / 18:43:51 / cg"
! !

!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,
     interpreted in the UTC timezone."

    ^ 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:0 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

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

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 
        millisecond:0
    "
     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"
!

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

    ^ self basicNew setSeconds:secs.

    "
     Timestamp secondsSince1970:0      
     Timestamp secondsSince1970:3600
     Timestamp secondsSince1970:3600*24
     (Timestamp year:2010 month:7 day:1 hour:0 minute:0 second:0)
       =
     (Timestamp secondsSince1970:1277935200)
    "

    "Created: / 21-10-1996 / 17:48:30 / stefan"
    "Modified: / 13-07-1999 / 12:31:22 / stefan"
    "Modified: / 08-01-2011 / 16:06:28 / cg"
!

utcMillisecondsSince1970:secs
    "set time from elapsed milliseconds since 1-1-1970, 0:0:0."

    ^ self basicNew setMilliseconds:secs

    "Created: / 08-01-2011 / 16:09:32 / cg"
!

utcNow
    ^ UtcTimestamp now

    "
        Timestamp now
        Timestamp utcNow
    "
!

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

    ^ self secondsSince1970:secs

"/    |divMod|
"/
"/    divMod := secs 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  
    "

    "Modified: / 13-07-1999 / 12:31:22 / stefan"
    "Created: / 08-01-2011 / 16:05:09 / cg"
!

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:7 day:1 hour:1 minute: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 
            year:y month:m day:d hour:h minute:min second:s millisecond: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:7 day:1 hour:1 minute:0 second:0 
     UtcTimestamp year:2000 month:7 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:'Compatibility-Squeak'!

current
    ^ self now
!

fromString: aString
    "Answer a new instance for the value given by aString"

    ^ self readFrom: (ReadStream on: aString).

    "
     Timestamp fromString: '1-10-2000 11:55:00 am'. 
    "

    "Modified (format): / 20-08-2011 / 16:51:53 / cg"
!

readFrom:aStringOrStream
    "Answer a new instance for the value given by aStringOrStream"

    ^ self 
        readFrom:aStringOrStream 
        onError:[ ConversionError raiseRequestErrorString:'conversion error']

    "
     self readFrom:'23-jun-2000 15:00'
     self readFrom:'23-jun-2000 '
    "

    "Modified (comment): / 20-08-2011 / 16:52:10 / cg"
! !

!Timestamp class methodsFor:'format strings'!

defaultFormatString
    ^ '%(year)-%(month)-%(day) %h:%m:%s.%i'

    "Created: / 16-01-2011 / 11:23:36 / cg"
! !

!Timestamp class methodsFor:'obsolete'!

day:d month:m year:y hour:h minutes:min seconds:s
    <resource: #obsolete>
    "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


    "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
    <resource: #obsolete>
    "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"
! !

!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:[TimeConversionError 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:[ TimeConversionError raiseErrorString:' - bad day' ].
    (month between:1 and:12) ifFalse:[ TimeConversionError raiseErrorString:' - bad month' ].

    [aStream peek isDigit] whileFalse:[aStream next].
    year := Integer readFrom:aStream onError:[ TimeConversionError 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:[ TimeConversionError raiseErrorString:' - bad hour' ].

        [aStream peek isDigit] whileFalse:[aStream next].
        min := Integer readFrom:aStream onError:-1.
        (min between:0 and:59) ifFalse:[ TimeConversionError 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:[ TimeConversionError raiseErrorString:' - bad second' ].

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

     UtcTimestamp 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 representation from aStream.

     If the time ends with a 'Z' it is the UTC (or zulu) time,
     othrwise it is local time.

     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 isUtcTime peekChar|

    str := aStringOrStream readStream.

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

    yearOrNil notNil ifTrue:[
        year := yearOrNil
    ] ifFalse:[
        year := Integer readFrom:str onError:nil.
        year isNil ifTrue:[ TimeConversionError raiseErrorString:' - bad year' ]
    ].

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

        str skipSeparators.
        str peek == $- ifTrue:[
            str next.
            "/ day follows.
            day := Integer readFrom:str.
            (day between:1 and:31) ifFalse:[ TimeConversionError 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:[ TimeConversionError raiseErrorString:' - bad hour' ].
        str skipSeparators.
        str peekOrNil == $: ifTrue:[
            str next.
            "/ minutes follow.
            min := Integer readFrom:str onError:-1.
            (min between:0 and:59) ifFalse:[ TimeConversionError raiseErrorString:' - bad minute' ].
            str skipSeparators.
            str peekOrNil == $: ifTrue:[
                str next.
                "/ seconds follow.
                sec := Integer readFrom:str onError:-1.
                (sec between:0 and:59) ifFalse:[ TimeConversionError raiseErrorString:' - bad seconds' ].
                str skipSeparators.
                str peekOrNil == $. ifTrue:[
                    str next.
                    "/ millis follow.
                    fraction := Number readMantissaFrom:str radix:10.    
                    millis := (1000 * fraction) rounded.  "/ mhmh - should it be truncated ?
                ]
            ].
        ].
        
        peekChar := str peekOrNil.
        peekChar notNil ifTrue:[
            peekChar == $Z ifTrue:[
                str next.
                isUtcTime := true.
            ]
"/ Todo
"/            ifFalse:[peekChar == $+ ifTrue:[
"/                str next.
"/                isUtcTime := true.
"/            ] ifFalse:[peekChar == $- ifTrue:[
"/                str next.
"/                isUtcTime := true.
"/            ]]]
        ].
    ].

    "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:[ TimeConversionError raiseErrorString:' - bad hour' ].
    ].

    isUtcTime ifTrue:[
        ^ self 
            UTCYear:year month:month day:day 
            hour:hour minute:min second:sec millisecond:millis.
    ] ifFalse:[
        ^ 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:06Z'    

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

    |retVal|

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

!Timestamp class methodsFor:'reading'!

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 format read here is either
        yyyymmddHHMMSS.iii+uuuu, which is the ASN1 GeneralizedTime format.
     or:
        yyyy-mm-dd HH:MM:SS.iii +uuuu.
     The string is interpreted as 24 hour format, as printed.

     This format is used for BER specification of the ASN.1 GeneralizedTime as defined in X.208 Sec. 33,
     so read this before changing anything here.

     Notice, that this is not the storeString format and 
     is different from the format expected by readFrom:.
    "
    ^ self 
        readGeneralizedFrom:aStringOrStream
        short:false
        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 format read here is either
        yyyymmddHHMMSS.iii+uuuu, which is the ASN1 GeneralizedTime format.
     or:
        yyyy-mm-dd HH:MM:SS.iii +uuuu.
     The string is interpreted as 24 hour format, as printed.

     This format is used for BER specification of the ASN.1 GeneralizedTime as defined in X.208 Sec. 33,
     so read this before changing anything here.

     Notice, that this is not the storeString format and 
     is different from the format expected by readFrom:.
    "

    ^ self readGeneralizedFrom:aStringOrStream short:false onError: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"
!

readGeneralizedFrom:aStringOrStream short:shortFormat onError:exceptionBlock
    "return a new Timestamp, reading a printed representation from aStream.
     The long format read here is either
            yyyymmddHHMMSS.iii+uuuu, which is the ASN1 GeneralizedTime format.
        or:
            yyyy-mm-dd HH:MM:SS.iii +uuuu.
     The (not recommended) short forms are:
            yymmddHHMMSS.iii+uuuu, which is the ASN1 GeneralizedTime format.
        or:
            yy-mm-dd HH:MM:SS.iii +uuuu.
     The string is interpreted as 24 hour format, as printed.

     This format is used for BER specification of the ASN.1 GeneralizedTime and
     UTCTime as defined in X.208 Sec. 33, so read this before changing anything here.
     The short form is no longer recommended.

     Notice, that this is not the storeString format and 
     is different from the format expected by readFrom:.
    "


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

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

        shortFormat ifTrue:[
            year := Integer readFrom:(str next:2).
            year < 50 ifTrue:[
                year := year + 2000.
            ] ifFalse:[
                year := year + 1900.
            ].
        ] ifFalse:[
            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:[]

     Timestamp readGeneralizedFrom:'20080718120000+0300' short:false onError:[] 
     Timestamp readGeneralizedFrom:'080718120000+0300' short:true onError:[]    
     Timestamp readGeneralizedFrom:'990718120000+0300' short:true 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"
!

readISO8601From: stringOrStream

    ^ TimestampISO8601Builder read:stringOrStream withClass:self

    "Created: / 16-06-2005 / 16:13:36 / masca"
!

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
!

readRFC1123FormatFrom:rfc1123String onError:exceptionBlock
    |parts indexModifier utcOffsetString utcOffset day year time monthName month|

"/    All HTTP/1.0 date/time stamps must be represented in Universal Time (UT), 
"/    also known as Greenwich Mean Time (GMT), without exception. 
"/    This is indicated in the first two formats by the inclusion of "GMT" as the three-letter abbreviation for time zone, 
"/    and should be assumed when reading the asctime format.
"/
"/    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"
"/
"/    Mon, 17 Aug 2009 11:11:15 GMT

    rfc1123String isEmptyOrNil ifTrue:[^ exceptionBlock value].

    parts := rfc1123String subStrings:Character space.
    parts size == 6 ifTrue:[
        indexModifier := 0.
    ] ifFalse:[
        parts size == 5 ifTrue:[
            indexModifier := -1.
        ] ifFalse:[
            ^ exceptionBlock value
        ].
    ].

    utcOffset := 0.
    utcOffsetString := (parts at:6 + indexModifier).
    ((utcOffsetString sameAs:'GMT') or:[utcOffsetString sameAs:'UTC']) ifFalse:[ 
        self assert:utcOffsetString size == 5.

        utcOffset := (utcOffsetString from:4 to:5) asString asNumber * 60.
        utcOffset := utcOffset + ((utcOffsetString from:2 to:3) asString asNumber * 60 * 60).

        (utcOffsetString at:1) asSymbol == #- ifTrue:[
            utcOffset := -1 * utcOffset.
        ].
    ].

    day := Integer readFrom:(parts at:2 + indexModifier) onError:[^ exceptionBlock].
    year := Integer readFrom:(parts at:4 + indexModifier) onError:[^ exceptionBlock].
    time := Time readFrom:(parts at:5 + indexModifier) onError:[^ exceptionBlock].
    monthName := parts at:3 + indexModifier.

    month := (1 to:12) asOrderedCollection detect:[:i | 
        (Date abbreviatedNameOfMonth:i language:#en) sameAs:monthName 
    ] ifNone:[^ exceptionBlock].    

    ^ (self 
        fromDate:(Date newDay:day monthIndex:month year:year) 
        andTime:time) + utcOffset

    "Modified: / 05-10-2010 / 16:05:32 / cg"
! !


!Timestamp methodsFor:'accessing'!

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

    ^ self timeInfo 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)"

    ^ self timeInfo 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."

    ^ self timeInfo dayInYear

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

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

dayOfMonth
    "Answer the day of the month represented by me.
     Same as day; for ST-80 compatibility."

    ^ self asDate dayOfMonth

    "
     Timestamp now dayOfMonth 
     (Timestamp newDay:184 year:1996) dayOfMonth  
    "

    "Created: / 20-01-2011 / 12:26:54 / cg"
!

dayOfWeekName
    "return the week-day of the receiver as a string.
     The returned string depends on the language setting.
     Expect things like 'monday', 'tuesday' ..."

    ^ self asDate dayOfWeekName

    "
     Timestamp now dayOfWeekName 
     (Timestamp newDay:184 year:1996) dayOfWeekName  
    "

    "Created: / 20-01-2011 / 12:28:46 / 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)"

    ^ self timeInfo 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)"

    ^ self timeInfo 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)"

    ^ self timeInfo 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."

    ^ self timeInfo 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)"

    ^ self timeInfo seconds

    "
     Timestamp now seconds 
    "

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

timeInfo
    ^ OperatingSystem computeTimeAndDateFrom:osTime
!

timeZoneDeltaInMinutes
    "answer the number of minutes between local time and utc time.
     Delta is positive if local time is ahead of utc, negative if behind utc."

    ^ self utcOffset negated // 60

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

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

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

    ^ self timeInfo 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"
!

weekInYear
    "return the week number of the receiver - 1 for Jan, 1st."

    ^ Date weekInYearOf:self

    "
     (Timestamp newDay:1 year:2000) weekInYear    
     (Timestamp newDay:2 year:2000) weekInYear    
     (Timestamp newDay:3 year:2000) weekInYear    
    "
!

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

    ^ self timeInfo year

    "
     Timestamp now year
    "

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

!Timestamp methodsFor:'arithmetic'!

ceilingSecond
    "return a timestamp which represents the next full second"

    |offs|

    offs := (self milliseconds / 1000) ceiling.
    ^ self class basicNew setSeconds:(self getSeconds + offs).

    "
     |t1 t2|

     t1 := Timestamp now.
     t2 := t1 ceilingSecond.
     self halt
    "

    "Created: / 08-01-2011 / 16:23:03 / cg"
!

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

    ^ 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"
    "Modified: / 10-07-2010 / 09:37:01 / cg"
!

floorSecond
    "return a timestamp truncated to the last full second"

    ^ self class basicNew setSeconds:(self getSeconds).

    "
     |t1 t2|

     t1 := Timestamp now.
     t2 := t1 floorSecond.
     self halt
    "

    "Created: / 08-01-2011 / 16:20:55 / cg"
!

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

    ^ self getMilliseconds - (aTimestamp getMilliseconds)

    "
     |t1 t2|

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

    "Modified: / 10-07-2010 / 09:37:18 / cg"
!

roundedToSecond
    "return a timestamp which represents the time rounded to the nearest full second"

    |offs|

    offs := (self milliseconds / 1000) rounded.
    ^ self class basicNew setSeconds:(self getSeconds + offs).

    "
     |t1 t2|

     t1 := Timestamp now.
     t2 := t1 roundedToSecond.
     self halt
    "

    "Created: / 08-01-2011 / 16:24:12 / cg"
!

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

    ^ self getSeconds - (aTimestamp getSeconds)

    "
     |t1 t2|

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

    "Modified: / 10-07-2010 / 09:37:24 / cg"
! !

!Timestamp methodsFor:'comparing'!

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

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

    ^ self timeInfo asDate 

    "
     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
    "represent myself as a timestamp in the local timezone"

    ^ self

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

    ^ self timeInfo asTime

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

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

    ^ self 
!

asUtcTimestamp
    "represent myself as a timestamp in the UTC timezone"
    
    ^ UtcTimestamp fromOSTime:osTime

    "
     Timestamp now asUtcTimestamp
     Timestamp now asUtcTimestamp asLocalTimestamp
    "
!

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:'double dispatching'!

differenceFromTimestamp:aTimestamp
    "/ the correct thing to do (and I will, in the future) is to
    "/ return a TimeDuration:
    "/
    "/ ^ TimeDuration fromMilliseconds:(self getMilliseconds - (aTimestamp getMilliseconds))
    "/ which is the same as: deltaFrom:aTimestamp
    "/
    "/ however, there might me old code around, which might not be prepared for
    "/ getting a non-number (the seconds). Therefore, for the meantime,
    "/ we return:

    ^ aTimestamp getSeconds - self getSeconds
    "/ which is the same as: secondDeltaFrom:aTimestamp

    "/ be prepared for a change here.

    "Created: / 01-08-2011 / 16:38:10 / cg"
! !

!Timestamp methodsFor:'initialization'!

year:y month:m day:d hour:h minute:min second:s millisecond:millis 
    osTime := OperatingSystem 
                computeOSTimeFromYear:y
                month:m
                day:d
                hour:h
                minute:min
                seconds:s
                millis:millis
! !


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

    self printGeneralizedOn:aStream isLocal:isLocal short:false


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

printGeneralizedOn:aStream isLocal:isLocal short:shortFormat
    "append a representation of the receiver to aStream in a general format,
     top-down, without separators;
        long format:  'yyyymmddHHMMSS.mmm+0100'
        short format: 'yymmddHHMMSS.mmm+0100'

     This format is used for the ASN.1 GeneralizedTime and UTCTime
     as defined in X.208 Sec. 33, so read this before changing the output format.
     The short format is no longer recommended.

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

    |t off|

    isLocal ifTrue:[
        t := self timeInfo.
    ] ifFalse:[
        t := self asUtcTimestamp timeInfo.
    ].

    shortFormat ifTrue:[
        self assert:(t year between:1951 and:2049).
        (t year \\ 100) printOn:aStream leftPaddedTo:2 with:$0.
    ] ifFalse:[
        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.
        (self isUtcTimestamp or:[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 now printGeneralizedOn:Transcript isLocal:true. Transcript cr. 
     (Timestamp fromSeconds:0) printGeneralizedOn:Transcript. Transcript cr.
     Time now printOn:Transcript. Transcript cr.           
     Date today printOn:Transcript. Transcript cr.        

     Timestamp now printGeneralizedOn:Transcript isLocal:false short:false. Transcript cr. 
     UtcTimestamp now printGeneralizedOn:Transcript isLocal:false short:false. 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"
!

printISO8601

    ^ TimestampISO8601Builder print: self

    "
     Timestamp now printISO8601           
    "

    "Created: / 16-06-2005 / 16:11:15 / masca"
!

printISO8601Compressed

    ^ TimestampISO8601Builder printCompressed: self

    "
     Timestamp now printISO8601Compressed           
    "

    "Created: / 16-06-2005 / 16:11:31 / masca"
!

printISO8601CompressedOn: aStream

    TimestampISO8601Builder printCompressed: self on: aStream

    "Created: / 16-06-2005 / 16:11:50 / masca"
!

printISO8601On: aStream

    TimestampISO8601Builder print: self on: aStream

    "Created: / 16-06-2005 / 16:11:07 / masca"
!

printIso8601FormatOn:aStream
    "append the iso8601 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.

     No timezone information (eg. Z or +0100) is added, so the reader will read as local time."

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

    |timeInfo|

    timeInfo := self asUtcTimestamp 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 is too slow for heavy use    
"/    timeInfo printOn:aStream format:'%(ShortDayName), %(day) %(ShortMonthName) %y %h:%m:%s GMT' language:#en. 

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

    "
     String streamContents:[:s| Timestamp now printRFC1123FormatOn:s]   
    "
!

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

isTimestamp
    ^ true
!

isUtcTimestamp
    ^ false
! !

!Timestamp methodsFor:'visiting'!

acceptVisitor:aVisitor with:aParameter
    ^ aVisitor visitTimestamp:self with:aParameter
! !

!Timestamp::TimestampBuilderAbstract methodsFor:'error reporting'!

malformed:aString
    TimeConversionError raiseErrorString:(' - ', aString)

    "Created: / 15-06-2005 / 15:54:04 / masca"
! !

!Timestamp::TimestampBuilderAbstract methodsFor:'support'!

addHoursAndMinutes: arrayWithHoursAndMinutes
    "Add the given number of hours and minutes to the current timestamp state. If the time
    is to be subtracted, both numbers in the array must be negated. When the are not the same
    sign, the behavior may be strange. It's intended only for time zone corrections, where
    not more than 12 (in fact, 23) hours is added or subtracted (ie. date can be modified only
    one day forward or backward)."

    | hours minutes |
    hours := arrayWithHoursAndMinutes first.
    minutes := arrayWithHoursAndMinutes second.

    minutes isZero ifFalse: [
        minute := minute + minutes.
        minute >= 60 ifTrue: [
            hours := hours + minute // 60.
            minute := minute \\ 60.
        ].
        minute < 0 ifTrue: [
            hours := hours + minute // 60.
            minute := (minute \\ 60) negated
        ]
    ].

    "Hours may get zero by time zone specification or by minutes modifications above."
    hours isZero ifTrue: [^self].

    "Add or subtract the hour and make date corrections if necessary."
    hour := hour + hours.
    hour < 0 ifTrue: [
        "Oops, got to previous day, must adjust even the date."
        hour := 24 - ((hour negated) \\ 24).
        day := day - 1.
        day <= 0 ifTrue: [
            "Got to previous month..."
            month := month - 1.
            month <= 0 ifTrue: [year := year - 1. month := 12].
            day := self lastDayInMonth: month]
    ].
    hour >= 24 ifTrue: [
        hour := hour \\ 24.
        day := day + 1.
        day > (self lastDayInMonth: month) ifTrue: [
            month := month + 1.
            month > 12 ifTrue: [year := year + 1. month := 1].
            day := 1]
    ]

    "Created: / 15-06-2005 / 16:45:49 / masca"
    "Modified: / 16-06-2005 / 15:04:45 / masca"
!

dateFromDayNumber: anInteger
    "Set month and day from an absolute number of the day in the year. 1.1. is day number one."

    | leap |
    leap := self isLeapYear: year.

    (anInteger between: 1 and: 365) ifFalse: [
        (leap and: [anInteger = 366])
            ifFalse: [self malformed: 'Bad day number: ' , anInteger printString]
    ].

    self shouldImplement

    "Created: / 15-06-2005 / 11:27:35 / masca"
    "Modified: / 16-06-2005 / 12:31:37 / masca"
!

dateFromWeek: weekInteger andWeekday: dayInteger
    "Compute the month and day. Find the first day (weekday) in the year, maybe even
    adjust the year. Both week and day are 1-based, the first week in a year is the one
    with thursday (or the one containing 4.1.)."

    "Check numbers. Year may be checked if it contains 53 weeks or 52 weeks only."
    (dayInteger between: 1 and: 7) ifFalse: [self malformed: 'Bad weekday number: ' , dayInteger printString].
    (weekInteger between: 1 and: 53) ifFalse: [self malformed: 'Bad week number: ' , weekInteger printString].

    self shouldImplement

    "Created: / 15-06-2005 / 11:29:42 / masca"
    "Modified: / 15-06-2005 / 16:42:33 / masca"
!

isAllowedDay: anInteger
    "Answer whether the given day is allowed in the current month."

    ^anInteger between: 1 and: (self lastDayInMonth: month)

    "Created: / 15-06-2005 / 16:22:51 / masca"
!

isLeapYear: anInteger

    ^(anInteger bitAnd: 3) = 0 and: [anInteger \\ 100 > 0 or: [anInteger \\ 400 = 0]]

    "Created: / 15-06-2005 / 16:16:31 / masca"
!

lastDayInMonth: anInteger
    "Answer the number of the last day of the given month in the current year."

    ^anInteger = 2
        ifTrue: [(self isLeapYear: year) ifTrue: [29] ifFalse: [28]]
        ifFalse: [#(31 28 31 30 31 30 31 31 30 31 30 31) at: month]

    "Created: / 15-06-2005 / 17:12:31 / masca"
!

timestampWithClass:timestampClass
    "Answer the timestamp as it has been parsed."
    "Notes:
     - When reading, the time has either been adjusted to UTZ/zulu time,
       or is a local time.
     - On UNIX, timestamps can only hold dates between 1970-01-01T01:00:00Z and 2038-01-19T00:00:00Z"

    isUtcTime ifTrue:[
        ^ timestampClass
            UTCYear: year month: month day: day
            hour: hour minute: minute second: second millisecond: millisecond
    ] ifFalse:[
        ^ timestampClass
            year: year month: month day: day
            hour: hour minute: minute second: second millisecond: millisecond
    ]

    "Created: / 15-06-2005 / 15:39:24 / masca"
    "Modified: / 30-06-2005 / 16:48:25 / masca"
! !

!Timestamp::TimestampISO8601Builder class methodsFor:'documentation'!

documentation
"
    TimestampISO8601Builder is designed to read any (almost) format of ISO 8601 encoded timestamp. Also, class
    methods can be used to print but the main reading job is done in instance protocol. It has been
    written because of insufficient abilities of Timestamp #readIso8601FormatFrom: method.

    It produces timestamps, ie. when the string (or stream) contains only a time, an error will result
    (it may also pass in some cases but with the time undestood as date). It survives incomplete dates,
    broken years, incomplete times and timezones. All times read with timezone difference are recomputed
    to UTC before the timestamp is created (even passing across new year boundary is handled correctly).
    Unknown offsets (usually local) are considered UTC - this may be wrong and more work is probably needed.
    All data is checked for validity (including leap years, leap seconds,...) during reading and as soon as
    possible. For an example of what the builder can read, see the examples method and ISO 8601 itself.

    [author:]
        Martin Dvorak (masca@volny.cz)

    [instance variables:]
        stream          A stream the builder operates on. Assigned on each call to instance method #read:,
                        so the builder instance can be reused (by at most one thread).
        year            Current timestamp year. No default value, date must be present.
        month           Current timestamp month. May change during parsing. Defaults to 1.
        day             Current timestamp day. Defaults to 1.
        hour            Current timestamp hour. Defaults to 0.
        minute          Current timestamp minute. Defaults to 0.
        second          Current timestamp second. Defaults to 0.
        millisecond     Current timestamp millisecond. Defaults to 0.

    [see also:]
        Timestamp
"
!

examples
"
    See the testing protocol on instance protocol (should be turned into a TestCase).
    It covers the main features this builder has.

    Just to introduce some coding examples, try:
        Timestamp readISO8601From: (TimestampISO8601Builder print: Timestamp now)
        UtcTimestamp readISO8601From: (TimestampISO8601Builder print: UtcTimestamp now)
        Timestamp readISO8601From: (TimestampISO8601Builder print: UtcTimestamp now)
"
!

history
    "Created: / 16-06-2005 / 16:28:38 / masca"
! !

!Timestamp::TimestampISO8601Builder class methodsFor:'parsing'!

read: stringOrStream withClass:timestampClass
    ^ self new read:stringOrStream withClass:timestampClass

    "Created: / 15-06-2005 / 17:52:03 / masca"
! !

!Timestamp::TimestampISO8601Builder class methodsFor:'printing'!

print: aTimestamp
    "Print the given timestamp in general ISO8601 format."

    | stream |
    stream := '' writeStream.
    self print: aTimestamp on: stream.
    ^ stream contents

    "Created: / 15-06-2005 / 17:52:29 / masca"
!

print: aTimestamp on: aStream
    "Print the given timestamp in general ISO8601 format."

    |timeInfo|

    timeInfo := aTimestamp asUtcTimestamp timeInfo.

    aStream
        nextPutAll: (timeInfo year printStringRadix: 10 size: 4 fill: $0);
        nextPut: $-;
        nextPutAll: (timeInfo month printStringRadix: 10 size: 2 fill: $0);
        nextPut: $-;
        nextPutAll: (timeInfo day printStringRadix: 10 size: 2 fill: $0);
        nextPut: $T;
        nextPutAll: (timeInfo hours printStringRadix: 10 size: 2 fill: $0);
        nextPut: $:;
        nextPutAll: (timeInfo minutes printStringRadix: 10 size: 2 fill: $0);
        nextPut: $:;
        nextPutAll: (timeInfo seconds printStringRadix: 10 size: 2 fill: $0);
        nextPut: $Z

    "Created: / 15-06-2005 / 17:56:51 / masca"
!

printCompressed: aTimestamp
    "Print in special compressed format for timestamp interchange with mobile devices."

    | stream |
    stream := '' writeStream.
    self printCompressed: aTimestamp on: stream.
    ^ stream contents

    "Created: / 15-06-2005 / 17:52:52 / masca"
!

printCompressed: aTimestamp on: aStream

    |timeInfo|

    timeInfo := aTimestamp asUtcTimestamp timeInfo.

    aStream
        nextPutAll: (timeInfo year printStringRadix: 10 size: 4 fill: $0);
        nextPutAll: (timeInfo month printStringRadix: 10 size: 2 fill: $0);
        nextPutAll: (timeInfo day printStringRadix: 10 size: 2 fill: $0);
        nextPut: $T;
        nextPutAll: (timeInfo hours printStringRadix: 10 size: 2 fill: $0);
        nextPutAll: (timeInfo minutes printStringRadix: 10 size: 2 fill: $0);
        nextPutAll: (timeInfo seconds printStringRadix: 10 size: 2 fill: $0);
        nextPut: $Z

    "Created: / 15-06-2005 / 17:54:17 / masca"
! !

!Timestamp::TimestampISO8601Builder class methodsFor:'testing'!

test

    self test_date.
    self test_time.
    self test_timezone.
    self test_edge.

    "
        TimestampISO8601Builder test
    "

    "Created: / 15-06-2005 / 17:51:16 / masca"
    "Modified: / 16-06-2005 / 10:15:55 / masca"
!

test_date

    | ts |
    ts := UtcTimestamp
         year: 2005 month: 6 day: 15
         hour: 0 minute: 0 second: 0 millisecond: 0.

    "Test common dates"
    self assert: ts = (self read: '20050615' withClass:Timestamp).
    self assert: ts = (self read: '2005-06-15'  withClass:Timestamp).
    self assert: ts = (self read: '05-06-15'  withClass:Timestamp).
    self assert: ts = (self read: '05-0615'  withClass:Timestamp). "/ Is this correct?
    self assert: ts = (self read: ':50615'  withClass:Timestamp). "/ Should not happen and should not appear after 2009
    self assert: ts = (self read: '200506-15'  withClass:Timestamp). "/ Is this corect?
    self assert: ts = (self read: '105-06-15'  withClass:Timestamp). "/ Should not happen

    "Test week numbers"
    "/self assert: ts = (self read: '05W243'  withClass:Timestamp).
    "/self assert: ts = (self read: '2005W24-3'  withClass:Timestamp).

    "Test day numbers"
    "self assert: ts = (self read: '2005-166'  withClass:Timestamp).

    ts := Timestamp year: 2004 month: 12 day: 31 hour: 0 minute: 0 second: 0 millisecond: 0.
    self assert: ts = (self read: '2004-366'  withClass:Timestamp).

    ts := Timestamp year: 2005 month: 12 day: 31 hour: 0 minute: 0 second: 0 millisecond: 0.
    self assert: ts = (self read: '2004-365'  withClass:Timestamp)."

    "Test february"
    ts := UtcTimestamp year: 2000 month: 2 day: 28 hour: 0 minute: 0 second: 0 millisecond: 0.
    self assert: ts = (self read: '20000228'  withClass:Timestamp).

    ts := UtcTimestamp year: 2000 month: 2 day: 29 hour: 0 minute: 0 second: 0 millisecond: 0.
    self assert: ts = (self read: '20000229'  withClass:Timestamp).

    "
        TimestampISO8601Builder new test_date
    "


    "Created: / 15-06-2005 / 17:21:56 / masca"
    "Modified: / 16-06-2005 / 11:50:04 / masca"
!

test_edge

    | ts |

    self test_mustFail: [self read: '20050229' withClass:Timestamp].
    self test_mustFail: [self read: '20050029' withClass:Timestamp].
    self test_mustFail: [self read: '20050332' withClass:Timestamp].
    self test_mustFail: [self read: '2005-366' withClass:Timestamp].

    ts := UtcTimestamp year: 2005 month: 1 day: 1 hour: 0 minute: 0 second: 0 millisecond: 0.
    self assert: ts = (self read: '20041231T22-0200' withClass:Timestamp).

    ts := UtcTimestamp year: 2004 month: 12 day: 31 hour: 22 minute: 0 second: 0 millisecond: 0.
    self assert: ts = (self read: '20050101T0000+0200' withClass:Timestamp).

    "
        TimestampISO8601Builder new test_edge
    "


    "Created: / 16-06-2005 / 09:44:34 / masca"
    "Modified: / 16-06-2005 / 11:48:59 / masca"
!

test_mustFail: aBlock

    TimeConversionError
        handle: [:ex | ex return]
        do: [
            aBlock value.
            self error: 'Assertion failed'
        ]

    "Created: / 16-06-2005 / 09:43:37 / masca"
!

test_time

    | ts |

    ts := UtcTimestamp  year: 2005 month: 6 day: 15 hour: 17 minute: 37 second: 0 millisecond: 0.
    self assert: ts = (self read: '2005-06-15 17:37' withClass:Timestamp).
    self assert: ts = (self read: '20050615T1737' withClass:Timestamp).
    self assert: ts = (self read: '05-0615T17:3700' withClass:Timestamp).

    ts := UtcTimestamp  year: 2005 month: 6 day: 15 hour: 17 minute: 37 second: 0 millisecond: 30.
    self assert: ts = (self read: '05-0615T17:3700.03' withClass:Timestamp).
    self assert: ts = (self read: '2005-06-15T17:37:00.0305486-00:00' withClass:Timestamp).

    "
        TimestampISO8601Builder new test_time
    "

    "Created: / 15-06-2005 / 17:39:26 / masca"
    "Modified: / 16-06-2005 / 11:54:30 / masca"
!

test_timezone

    | ts |
    ts := UtcTimestamp
         year: 2005 month: 6 day: 15
         hour: 17 minute: 37 second: 0 millisecond: 0.

    self assert: ts = (self read: '2005-06-15T17:37Z' withClass:UtcTimestamp).
    self assert: ts = (self read: '2005-06-15T17:37+0000' withClass:Timestamp).
    self assert: ts = (self read: '2005-06-15T17:37-00:00' withClass:Timestamp).
    self assert: ts = (self read: '2005-06-15T15:37:00-0200' withClass:Timestamp).
    self assert: ts = (self read: '2005-06-15T19:37:00+0200'withClass:Timestamp).

    "
        TimestampISO8601Builder new test_timezone
    "

    "Created: / 15-06-2005 / 17:40:23 / masca"
    "Modified: / 16-06-2005 / 10:17:57 / masca"
! !

!Timestamp::TimestampISO8601Builder methodsFor:'private-reading'!

nextDigit
    | char |
    char := stream peekOrNil.
    char isNil ifTrue: [^-1].

    ^char isDigit
        ifTrue: [
            stream next.
            char codePoint - $0 codePoint]
        ifFalse: [-1]

    "Created: / 14-06-2005 / 11:48:52 / masca"
!

nextDigitOrError

    | digit |
    digit := self nextDigit.
    ^ digit < 0
        ifTrue: [self malformed: 'No digit found']
        ifFalse: [digit]

    "Created: / 15-06-2005 / 10:57:00 / masca"
    "Modified: / 15-06-2005 / 17:22:52 / masca"
!

nextDigits: anInteger

    | char number |
    number := 0.
    anInteger timesRepeat: [
        char := stream peekOrNil.
        char ifNil: [self malformed: 'Stream does not contain all ' , anInteger printString , ' digits'].
        char isDigit
            ifTrue: [
                stream next.
                number := number * 10 + char codePoint - $0 codePoint]
            ifFalse: [self malformed: 'Requested ' , anInteger printString , ' digits not found']
    ].
    ^ number

    "Created: / 14-06-2005 / 11:57:22 / masca"
    "Modified: / 15-06-2005 / 15:54:29 / masca"
! !

!Timestamp::TimestampISO8601Builder methodsFor:'processing'!

read:stringOrStream withClass:timestampClass
    | peek |

    stream := stringOrStream readStream.

    month := day := 1.
    hour := minute := second := millisecond := 0.

    "Read the year. This will read and swallow up to four year digits."
    self readYear.

    "Check if date has been read, ie. T or space necountered. If yes, read the time.
    There is possible inconsistency - a dash may be read followed by T, which is not
    valid. But don't mind that, timestamps will be well-formatted in most cases."
    peek := stream peekOrNil.
    peek ifNil: [
        "End of stream, only year has been read."
        ^self timestampWithClass:timestampClass].
    peek = $- ifTrue: [
        "Skip the dash after year, if present."
        stream next.
        peek := stream peekOrNil].
    peek := peek asUppercase.

    (peek = $T or: [peek = Character space])
        ifTrue: [
            "Got time signature. Skip the signature, read time and answer the timestamp."
            stream next.
            self readTime.
            self readTimezone.
            ^ self timestampWithClass:timestampClass]
        ifFalse: [
            "Date not read completely yet, expecting month/day or week/day or day"
            peek = $W
                ifTrue: [
                    "Parse week number and (possibly) day number."
                    stream next.
                    self readWeekNumber]
                ifFalse: [
                    "Got digit, read month number followed by day or day number."
                    self readMonthOrDay]
        ].

    peek := stream peekOrNil.
    peek ifNil: [
        "End of stream, only year has been read."
        ^ self timestampWithClass:timestampClass].

    (peek asUppercase = $T or: [peek = Character space])
        ifTrue: [
            "Got time signature, expecting time follows. Otherwise only date was in the stream."
            stream next.
            self readTime.
            self readTimezone].

    ^ self timestampWithClass:timestampClass

    "Created: / 14-06-2005 / 11:45:04 / masca"
    "Modified: / 16-06-2005 / 10:15:35 / masca"
! !

!Timestamp::TimestampISO8601Builder methodsFor:'reading'!

readMilliseconds
    "Read an arbitrary number of digits representing milliseconds. As the timestamp can
    hold only integer amounts of milliseconds, don't mind the rest of the digits."

    | digit factor |

    factor := 100.

    [
        digit := self nextDigit.
        digit >= 0
    ] whileTrue: [
        factor > 0 ifTrue: [
            "Factor still > 0, did not read all three digits of mantissa."
            millisecond := digit * factor + millisecond.
            factor := (factor / 10) integerPart
        ]
    ].

    factor = 100 ifTrue: [self malformed: 'No digits after millisecond separator']

    "Created: / 15-06-2005 / 15:25:45 / masca"
!

readMonthOrDay
    "Read month number, optionally followed by day, or absolute day number (three digit)."

    | dayDigit1 dayDigit2 |
    month := self nextDigits: 2.

    stream peekOrNil = $-
        ifTrue: [
            "Got dash. Day number must follow."
            stream next.
            day := self nextDigits: 2.
            (self isAllowedDay: day) ifFalse: [self malformed: 'Bad day: ' , day printString].
            ^self].

    dayDigit1 := self nextDigit.
    dayDigit1 < 0 ifTrue: [
        "No more digits than month, leave day unspecified."
        (month between: 1 and: 12) ifFalse: [self malformed: 'Bad month: ' , month printString].
        ^self].

    dayDigit2 := self nextDigit.
    dayDigit2 < 0
        ifTrue: [
            "Read only three digits, this is absolute day number in a year."
            self dateFromDayNumber: month * 10 + dayDigit1]
        ifFalse: [
            "Read four digits. So there's month and day."
            (month between: 1 and: 12) ifFalse: [self malformed: 'Bad month: ' , month printString].
            day := dayDigit1 * 10 + dayDigit2.
            (self isAllowedDay: day) ifFalse: [self malformed: 'Bad day: ' , day printString]]

    "Created: / 15-06-2005 / 11:12:02 / masca"
    "Modified: / 16-06-2005 / 11:47:34 / masca"
!

readTime
    "Date read, don't mind it. Read only the time value."

    | peek |

    hour := self nextDigits: 2.
    (hour between: 0 and: 24) ifFalse: [self malformed: 'Bad hour: ' , hour printString].

    peek := stream peekOrNil.
    peek = $:
        ifTrue: [stream next]
        ifFalse: [(peek notNil and: [peek isDigit]) ifFalse: [^self]].

    minute := self nextDigits: 2.
    (minute between: 0 and: 59) ifFalse: [self malformed: 'Bad minute: ' , minute printString].

    peek := stream peekOrNil.
    peek = $:
        ifTrue: [stream next]
        ifFalse: [(peek notNil and: [peek isDigit]) ifFalse: [^self]].

    second := self nextDigits: 2.
    (second between: 0 and: 59) ifFalse: [
        "Seconds are usually in this range, do a special check for leap seconds."
        second <= 61
            ifTrue: [
                "Leap seconds can occur only on midnight on 31.12. or 30.6. Dont' check year
                as it's not deterministic."
                (minute = 59 and: [hour = 23 and: [(month = 12 and: [day = 31]) or: [month = 6 and: [day = 30]]]])
                    ifFalse: [self malformed: 'Bad leap second']]
            ifFalse: [self malformed: 'Bad second: ' , second printString]
    ].

    "Hour, minute and second read. Read appendices."
    stream peekOrNil = $.
        ifTrue: [
            "Read dot. Skip it and read milliseconds."
            stream next.
            self readMilliseconds].

    hour = 24 ifTrue: [
        (minute = 0 and: [second = 0 and: [millisecond = 0]])
            ifTrue: [
                "On 24 hour, advance to the next day."
                "hour := 0.
                self addMinutes: 1440"]
            ifFalse: [self malformed: 'Bad 24 hour (minutes, seconds and millis not 0)']
    ]

    "Created: / 14-06-2005 / 17:27:00 / masca"
    "Modified: / 30-06-2005 / 11:34:38 / masca"
!

readTimezone
    "Read time zone information. There are three possibilities of what can occur.
    If there is nothing more to read, the offset is unknown - this is treated as
    Zulu time as this may not be true."

    | peek |
    peek := stream peek.
    peek ifNil: [^self].
    peek := peek asUppercase.

    "If the time is in Zulu, don't modify the timestamp. This makes the machine
    run in Zulu time zone, maybe some corrections would be nice."
    peek = $Z
        ifTrue: [
            "Time read, skip Zulu signature and exit."
            isUtcTime := true.
            stream next.
            ^ self].

    peek = $+
        ifTrue: [
            "Read a plus, expect a negative time zone difference."
            isUtcTime := true.
            stream next.
            self addHoursAndMinutes: (self readTimezoneOffset collect: [:e | e negated]).
            ^ self].

    peek = $-
        ifTrue: [
            "Read a minus, expect positive time zone difference or unknown offset."
            isUtcTime := true.
            stream next.
            self addHoursAndMinutes: self readTimezoneOffset.
            ^ self].

    "This is local time"
    isUtcTime := false.

    "Created: / 16-06-2005 / 09:54:21 / masca"
!

readTimezoneOffset
    "Read time zone offset as a number minutes. Generally, there should be hours only
    but as the format introduces minutes in offsets, we must accept them."

    | hours digit |

    "Read hours."
    hours := self nextDigits: 2.
    (hours between: 0 and: 12) ifFalse: [self malformed: 'Bad offset hour: ' , hours printString].

    stream peekOrNil = $:
        ifTrue: [
            "Colon read, minutes must follow."
            stream next.
            digit := self nextDigits: 2.
            (digit between: 0 and: 59) ifFalse: [self malformed: 'Bad offset minute: ' , digit printString].
            ^Array with: hours with: digit].

    "Read next digit and check whether minutes follow. If not, return only with hours. If yes,
     check boundaries."
    digit := self nextDigit.
    digit < 0 ifTrue: [^Array with: hours with: 0].
    digit >= 6 ifTrue: [self malformed: 'Bad offset minute: ' , (digit * 10) printString].

    "Read the last digit of offset, it must be present."
    ^Array with: hours with: digit * 10 + self nextDigitOrError

    "Created: / 15-06-2005 / 15:35:41 / masca"
    "Modified: / 15-06-2005 / 17:45:58 / masca"
!

readWeekNumber

    | week day digit |
    "Read week number. It is always two digits long."
    week := self nextDigits: 2.

    stream peekOrNil = $-
        ifTrue: [
            "Got dash, day number must follow."
            stream next.
            digit := self nextDigit.
            digit < 0 ifTrue: [self malformed: 'Bad weekday number'].
            self dateFromWeek: week andWeekday: digit.
            ^self].

    "Read day number that follows the week. If the number is not given, consider it monday."
    day := self nextDigit.
    day <= 0 ifTrue: [day := 1].

    self dateFromWeek: week andWeekday: day

    "Created: / 14-06-2005 / 12:06:47 / masca"
    "Modified: / 15-06-2005 / 15:53:34 / masca"
!

readYear
    "Read YYYY or :Y (broken decade) from the stream. Also handles correctly YY- and YYY-."

    | read peek |
    stream peekOrNil = $:
        ifTrue: [
            "Broken two digit year > 1999 follows."
            stream next.
            year := self nextDigitOrError + 2000.
            ^self].

    "Expecting two-, three- or four-digit year"
    "Read the first two digits. They must be there."
    read := self nextDigits: 2.

    "Check if there's a dash, this can help us deciding whether the year ends."
    peek := stream peekOrNil.
    peek ifNil: [^self].

    year := peek = $-
        ifTrue: [
            "OK, got two digits. These are expected to be the year after 1970."
            read < 70
                ifTrue: [read + 2000]
                ifFalse: [read + 1900]]
        ifFalse: [
            "Read the next digit for the case of three-digit year after 1900 (ie. year > 1999)."
             read := read * 10 + self nextDigitOrError.
             peek := stream peekOrNil.
             (peek isNil or: [peek = $-])
                ifTrue: [
                    "Read three digit year, return it."
                    read + 1900]
                ifFalse: [
                    "Read the fourth digit of the year. These can be month digits but the
                    two-digit year format is deprecated anyway."
                    read := read * 10 + self nextDigitOrError]
        ]

    "Created: / 14-06-2005 / 12:01:11 / masca"
    "Modified: / 15-06-2005 / 17:31:56 / masca"
! !

!Timestamp class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Timestamp.st,v 1.141 2011/09/15 08:42:09 ca Exp $'
!

version_CVS
    ^ '§Header: /cvs/stx/stx/libbasic/Timestamp.st,v 1.141 2011/09/15 08:42:09 ca Exp §'
!

version_SVN
    ^ '$Id: Timestamp.st 10761 2012-01-19 11:46:00Z vranyj1 $'
! !

Timestamp initialize!