abstract timestamp builder
authorfm
Tue, 22 Sep 2009 10:34:16 +0200
changeset 11993 f303ffa58005
parent 11992 1d7a1c1c1ccc
child 11994 4665bdb0fd89
abstract timestamp builder timestamp ISO 8601 builder
Timestamp.st
--- a/Timestamp.st	Mon Sep 21 18:48:48 2009 +0200
+++ b/Timestamp.st	Tue Sep 22 10:34:16 2009 +0200
@@ -18,6 +18,20 @@
 	category:'Magnitude-Time'
 !
 
+Object subclass:#TimestampBuilderAbstract
+	instanceVariableNames:'year month day hour minute second millisecond'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Timestamp
+!
+
+Timestamp::TimestampBuilderAbstract subclass:#TimestampISO8601Builder
+	instanceVariableNames:'stream'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Timestamp
+!
+
 !Timestamp class methodsFor:'documentation'!
 
 copyright
@@ -788,6 +802,15 @@
     ^ retVal
 ! !
 
+!Timestamp class methodsFor:'reading'!
+
+readISO8601From: stringOrStream
+
+    ^TimestampISO8601Builder read: stringOrStream
+
+    "Created: / 16-06-2005 / 16:13:36 / masca"
+! !
+
 !Timestamp methodsFor:'accessing'!
 
 day
@@ -1190,6 +1213,44 @@
     "
 ! !
 
+!Timestamp methodsFor:'printing'!
+
+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"
+! !
+
 !Timestamp methodsFor:'printing & storing'!
 
 addPrintBindingsTo:dict language:languageOrNil
@@ -1487,7 +1548,6 @@
     "
 ! !
 
-
 !Timestamp methodsFor:'visiting'!
 
 acceptVisitor:aVisitor with:aParameter
@@ -1495,10 +1555,759 @@
     ^ aVisitor visitTimestamp:self with:aParameter
 ! !
 
+!Timestamp::TimestampBuilderAbstract methodsFor:'error reporting'!
+
+malformed: aString
+
+    ConversionError 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"
+!
+
+timestamp
+    "Answer the timestamp as it has been parsed."
+    "Notes:
+     - Should use UTCYear:... here? This will produce timezone-dependent timestamp.
+     - On UNIX, timestamps can only hold dates between 1970-01-01T01:00:00Z and 2038-01-19T00:00:00Z"
+
+    ^Timestamp
+	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
+"
+    TimestampBuilder 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:
+	TimestampBuilder read: (TimestampBuilder print: Timestamp now)
+"
+!
+
+history
+    "Created: / 16-06-2005 / 16:28:38 / masca"
+! !
+
+!Timestamp::TimestampISO8601Builder class methodsFor:'parsing'!
+
+read: stringOrStream
+
+    ^self new read: stringOrStream
+
+    "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 := String new 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."
+
+    aStream
+	nextPutAll: (aTimestamp year printStringRadix: 10 size: 4 fill: $0);
+	nextPut: $-;
+	nextPutAll: (aTimestamp month printStringRadix: 10 size: 2 fill: $0);
+	nextPut: $-;
+	nextPutAll: (aTimestamp day printStringRadix: 10 size: 2 fill: $0);
+	nextPut: $T;
+	nextPutAll: (aTimestamp hour printStringRadix: 10 size: 2 fill: $0);
+	nextPut: $:;
+	nextPutAll: (aTimestamp minute printStringRadix: 10 size: 2 fill: $0);
+	nextPut: $:;
+	nextPutAll: (aTimestamp second 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 := String new writeStream.
+    self printCompressed: aTimestamp on: stream.
+    ^stream contents
+
+    "Created: / 15-06-2005 / 17:52:52 / masca"
+!
+
+printCompressed: aTimestamp on: aStream
+
+    aStream
+	nextPutAll: (aTimestamp year printStringRadix: 10 size: 4 fill: $0);
+	nextPutAll: (aTimestamp month printStringRadix: 10 size: 2 fill: $0);
+	nextPutAll: (aTimestamp day printStringRadix: 10 size: 2 fill: $0);
+	nextPut: $T;
+	nextPutAll: (aTimestamp hour printStringRadix: 10 size: 2 fill: $0);
+	nextPutAll: (aTimestamp minute printStringRadix: 10 size: 2 fill: $0);
+	nextPutAll: (aTimestamp second printStringRadix: 10 size: 2 fill: $0);
+	nextPut: $Z
+
+    "Created: / 15-06-2005 / 17:54:17 / masca"
+! !
+
+!Timestamp::TimestampISO8601Builder methodsFor:'private-reading'!
+
+nextDigit
+
+    | char |
+    char := stream peek.
+    char ifNil: [^-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 peek.
+	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
+
+    | 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 peek.
+    peek ifNil: [
+	"End of stream, only year has been read."
+	^self timestamp].
+    peek = $- ifTrue: [
+	"Skip the dash after year, if present."
+	stream next.
+	peek := stream peek].
+    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 timestamp]
+	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 peek.
+    peek ifNil: [
+	"End of stream, only year has been read."
+	^self timestamp].
+
+    (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 timestamp
+
+    "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 peek = $-
+	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 peek.
+    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 peek.
+    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 peek = $.
+	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."
+	    stream next.
+	    ^self].
+
+    peek = $+
+	ifTrue: [
+	    "Read a plus, expect a negative time zone difference."
+	    stream next.
+	    self addHoursAndMinutes: (self readTimezoneOffset collect: [:e | e negated]).
+	    ^self].
+
+    peek = $-
+	ifTrue: [
+	    "Read a minus, expect positive time zone difference or unknown offset."
+	    stream next.
+	    self addHoursAndMinutes: self readTimezoneOffset.
+	    ^self]
+
+    "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 peek = $:
+	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 peek = $-
+	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 peek = $:
+	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 peek.
+    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 peek.
+	     (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::TimestampISO8601Builder methodsFor:'testing'!
+
+test
+
+    self test_date.
+    self test_time.
+    self test_timezone.
+    self test_edge.
+
+    "
+        TimestampISO8601Builder new test
+    "
+
+    "Created: / 15-06-2005 / 17:51:16 / masca"
+    "Modified: / 16-06-2005 / 10:15:55 / masca"
+!
+
+test_date
+
+    | ts |
+    ts := Timestamp
+         year: 2005 month: 6 day: 15
+         hour: 0 minute: 0 second: 0 millisecond: 0.
+
+    "Test common dates"
+    self assert: ts = (self read: '20050615').
+    self assert: ts = (self read: '2005-06-15').
+    self assert: ts = (self read: '05-06-15').
+    self assert: ts = (self read: '05-0615'). "/ Is this correct?
+    self assert: ts = (self read: ':50615'). "/ Should not happen and should not appear after 2009
+    self assert: ts = (self read: '200506-15'). "/ Is this corect?
+    self assert: ts = (self read: '105-06-15'). "/ Should not happen
+
+    "Test week numbers"
+    "/self assert: ts = (self read: '05W243').
+    "/self assert: ts = (self read: '2005W24-3').
+
+    "Test day numbers"
+    "self assert: ts = (self read: '2005-166').
+
+    ts := Timestamp year: 2004 month: 12 day: 31 hour: 0 minute: 0 second: 0 millisecond: 0.
+    self assert: ts = (self read: '2004-366').
+
+    ts := Timestamp year: 2005 month: 12 day: 31 hour: 0 minute: 0 second: 0 millisecond: 0.
+    self assert: ts = (self read: '2004-365')."
+
+    "Test february"
+    ts := Timestamp year: 2000 month: 2 day: 28 hour: 0 minute: 0 second: 0 millisecond: 0.
+    self assert: ts = (self read: '20000228').
+
+    ts := Timestamp year: 2000 month: 2 day: 29 hour: 0 minute: 0 second: 0 millisecond: 0.
+    self assert: ts = (self read: '20000229').
+
+    "
+        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'].
+    self test_mustFail: [self read: '20050029'].
+    self test_mustFail: [self read: '20050332'].
+    self test_mustFail: [self read: '2005-366'].
+
+    ts := Timestamp year: 2005 month: 1 day: 1 hour: 0 minute: 0 second: 0 millisecond: 0.
+    self assert: ts = (self read: '20041231T22-0200').
+
+    ts := Timestamp year: 2004 month: 12 day: 31 hour: 22 minute: 0 second: 0 millisecond: 0.
+    self assert: ts = (self read: '20050101T0000+0200').
+
+    "
+        TimestampISO8601Builder new test_edge
+    "
+
+
+    "Created: / 16-06-2005 / 09:44:34 / masca"
+    "Modified: / 16-06-2005 / 11:48:59 / masca"
+!
+
+test_mustFail: aBlock
+
+    ConversionError
+	handle: [:ex | ex return]
+	do: [
+	    aBlock value.
+	    self error: 'Assertion failed'
+	]
+
+    "Created: / 16-06-2005 / 09:43:37 / masca"
+!
+
+test_time
+
+    | ts |
+
+    ts := Timestamp  year: 2005 month: 6 day: 15 hour: 17 minute: 37 second: 0 millisecond: 0.
+    self assert: ts = (self read: '2005-06-15 17:37').
+    self assert: ts = (self read: '20050615T1737').
+    self assert: ts = (self read: '05-0615T17:3700').
+
+    ts := Timestamp  year: 2005 month: 6 day: 15 hour: 17 minute: 37 second: 0 millisecond: 30.
+    self assert: ts = (self read: '05-0615T17:3700.03').
+    self assert: ts = (self read: '2005-06-15T17:37:00.0305486-00:00').
+
+    "
+        TimestampISO8601Builder new test_time
+    "
+
+    "Created: / 15-06-2005 / 17:39:26 / masca"
+    "Modified: / 16-06-2005 / 11:54:30 / masca"
+!
+
+test_timezone
+
+    | ts |
+    ts := Timestamp
+         year: 2005 month: 6 day: 15
+         hour: 17 minute: 37 second: 0 millisecond: 0.
+
+    self assert: ts = (self read: '2005-06-15T17:37Z').
+    self assert: ts = (self read: '2005-06-15T17:37+0000').
+    self assert: ts = (self read: '2005-06-15T17:37-00:00').
+    self assert: ts = (self read: '2005-06-15T15:37:00-0200').
+    self assert: ts = (self read: '2005-06-15T19:37:00+0200').
+
+    "
+        TimestampISO8601Builder new test_timezone
+    "
+
+    "Created: / 15-06-2005 / 17:40:23 / masca"
+    "Modified: / 16-06-2005 / 10:17:57 / masca"
+! !
+
 !Timestamp class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Timestamp.st,v 1.120 2009-08-24 14:18:40 sr Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Timestamp.st,v 1.121 2009-09-22 08:34:16 fm Exp $'
 ! !
 
 Timestamp initialize!