Timestamp.st
changeset 17006 d6ec5e448ac5
parent 17005 d6d98374dd39
child 17008 b3c0cf461687
--- a/Timestamp.st	Sat Nov 08 19:22:05 2014 +0100
+++ b/Timestamp.st	Mon Nov 10 15:05:02 2014 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -13,7 +13,7 @@
 
 AbstractTime subclass:#Timestamp
 	instanceVariableNames:'osTime'
-	classVariableNames:'Epoch EpochEnd EpochEndOSTime'
+	classVariableNames:'Epoch MinOSTime MaxOSTime'
 	poolDictionaries:''
 	category:'Magnitude-Time'
 !
@@ -38,7 +38,7 @@
 copyright
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -53,7 +53,7 @@
 "
     This class represents time values in milliSeconds starting some time in the past.
     When printing and accessing values like #hour,
-    the timestamp will be interpreted in the local timezone 
+    the timestamp will be interpreted in the local timezone
     (as opposed to UtcTimestamp, which presents itself in UTC,
      and as opposed to LocalTimestamp, which remembers the timezone in which it was created).
 
@@ -83,20 +83,20 @@
     AbsoluteTime is still kept as an alias for backward compatibility.
 
     Also Note:
-        On UNIX, osTime can only hold dates between 1970-01-01T00:00:00Z and 2038-01-19T00:00:00Z
-        However, timestamp instances can now hold negative osTime values (which are timestamps
-        before 1.1.1970 and greater than 4294967295 (2^32-1) for timestamps after 2038-01-19.
-
-        For dates before 1582 (when calendars were changed from Julian to Grgorian),
-        the so called 'proleptic gregorian calendar' is used. This assumes leap years to continue in
-        the past as if a gregorian calendar was used. Thus, 0000 is considered a leap year.
+	On UNIX, osTime can only hold dates between 1970-01-01T00:00:00Z and 2038-01-19T00:00:00Z
+	However, timestamp instances can now hold negative osTime values (which are timestamps
+	before 1.1.1970 and greater than 4294967295 (2^32-1) for timestamps after 2038-01-19.
+
+	For dates before 1582 (when calendars were changed from Julian to Grgorian),
+	the so called 'proleptic gregorian calendar' is used. This assumes leap years to continue in
+	the past as if a gregorian calendar was used. Thus, 0000 is considered a leap year.
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 
     [See also:]
-        UtcTimestamp Time Date
-        Delay ProcessorScheduler
+	UtcTimestamp Time Date
+	Delay ProcessorScheduler
 "
 ! !
 
@@ -106,7 +106,10 @@
 
     AbsoluteTime := self.       "backward compatibility"
 
-    EpochEndOSTime := self epochEnd osTime.
+    MinOSTime := 0.
+    MaxOSTime := 16r7FFFFFFF * 1000.
+
+    Epoch := UtcTimestamp basicNew setSeconds:0.
 ! !
 
 !Timestamp class methodsFor:'instance creation'!
@@ -116,7 +119,7 @@
      interpreted in the UTC timezone."
 
     ^ self basicNew
-            UTCyear:y month:m day:d hour:h minute:min second:s millisecond:millis
+	    UTCyear: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
@@ -137,30 +140,30 @@
     "decode a Timestamp literalArray.
 
      anArray may be:
-        #(Timestamp '200004182000.123')
+	#(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)
+	#(Timestamp #osTime: 12345678)
     "
 
     (anArray at:2) == #osTime: ifTrue:[
-        ^ self new osTime:(anArray at:3).
+	^ self new osTime:(anArray at:3).
     ].
 
     ^ self
-        readGeneralizedFrom:(anArray at:2)
-        onError:[ self conversionErrorSignal
-                    raiseErrorString:'literal array decoding' ]
+	readGeneralizedFrom:(anArray at:2)
+	onError:[ self conversionErrorSignal
+		    raiseErrorString:'literal array decoding' ]
 
     "
      Timestamp
-        decodeFromLiteralArray:#(Timestamp '20050323175226.014')
+	decodeFromLiteralArray:#(Timestamp '20050323175226.014')
      Timestamp
-        decodeFromLiteralArray:#(Timestamp '20050323175226.014-01')
+	decodeFromLiteralArray:#(Timestamp '20050323175226.014-01')
      Timestamp
-        decodeFromLiteralArray:#(Timestamp '20050323175226.014Z')
+	decodeFromLiteralArray:#(Timestamp '20050323175226.014Z')
     "
 !
 
@@ -168,29 +171,9 @@
     "the epoch is based to 0 for 1970-01-01 00:00:00.
      However, we allow negative values to represent timestamps before that"
 
-    Epoch isNil ifTrue:[
-        Epoch := UtcTimestamp new setSeconds:0.
-    ].
     ^ Epoch
 !
 
-epochEnd
-    "the epoch is based to 0 for 1970-01-01 00:00:00.
-     However, we allow negative values to represent timestamps before that"
-
-    EpochEnd isNil ifTrue:[
-        EpochEnd := UtcTimestamp new setSeconds:16r7FFFFFFF.
-    ].
-    ^ EpochEnd
-!
-
-epochEndOSTime
-    "the epoch ends at some OS dependent limit.
-     For now, hard wire this limit - should be an os query, to prepare for mktim64 to appear..."
-
-    ^ EpochEndOSTime.
-!
-
 fromDate:aDate
     "return an instance of the receiver, initialized from a time and a date
      object.
@@ -198,13 +181,13 @@
      from my superclass."
 
     ^ self
-        year:aDate year
-        month:aDate month
-        day:aDate day
-        hour:0
-        minute:0
-        second:0
-        millisecond:0
+	year:aDate year
+	month:aDate month
+	day:aDate day
+	hour:0
+	minute:0
+	second:0
+	millisecond:0
 
     "
      Timestamp fromDate:(Date today) andTime:(Time now)
@@ -224,13 +207,13 @@
      from my superclass."
 
     ^ self
-        year:aDate year
-        month:aDate month
-        day:aDate day
-        hour:aTime hours
-        minute:aTime minutes
-        second:aTime seconds
-        millisecond:aTime milliseconds
+	year:aDate year
+	month:aDate month
+	day:aDate day
+	hour:aTime hours
+	minute:aTime minutes
+	second:aTime seconds
+	millisecond:aTime milliseconds
 
     "
      Timestamp fromDate:(Date today) andTime:(Time now)
@@ -250,13 +233,13 @@
      Date protocol compatibility"
 
     ^ self
-        year:year
-        month:month
-        day:day
-        hour:0
-        minute:0
-        second:0
-        millisecond:0
+	year:year
+	month:month
+	day:day
+	hour:0
+	minute:0
+	second:0
+	millisecond:0
 
     "
      Timestamp newDay:1 month:1 year:1996
@@ -362,7 +345,7 @@
      from my superclass."
 
     ^ self basicNew
-            year:y month:m day:d hour:h minute:min second:s millisecond:millis
+	    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
@@ -386,8 +369,8 @@
     "Answer a new instance for the value given by aStringOrStream"
 
     ^ self
-        readFrom:aStringOrStream
-        onError:[ ConversionError raiseRequestWith:aStringOrStream errorString:' - timestamp']
+	readFrom:aStringOrStream
+	onError:[ ConversionError raiseRequestWith:aStringOrStream errorString:' - timestamp']
 
     "
      self readFrom:'23-jun-2000 15:00'
@@ -418,8 +401,8 @@
     "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
+	year:y month:m day:d hour:h
+	minute:min second:s millisecond:0
 
 
     "Modified: / 1.7.1996 / 15:22:26 / cg"
@@ -455,9 +438,9 @@
      it is assumed to be a year and the rest is read in iso8601 format.
 
      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.
+	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"
 
     |pos firstNumber secondNumber day month year hour min sec millis usFormat possibeMonthName ch utcOffsetOrNil|
@@ -465,9 +448,9 @@
     pos := aStream position.
     firstNumber := Integer readFrom:aStream onError:[TimeConversionError raiseErrorString:' - integer expected'].
     firstNumber > 31 ifTrue:[
-        "/ assume iso8601 format;
-        aStream position:pos.
-        ^ self readIso8601FormatFrom:aStream.
+	"/ assume iso8601 format;
+	aStream position:pos.
+	^ self readIso8601FormatFrom:aStream.
     ].
     aStream skipSeparators.
 
@@ -476,20 +459,20 @@
 
     [(ch := aStream peekOrNil) notNil and:[ch isLetterOrDigit]] whileFalse:[aStream next].
     ((ch := aStream peekOrNil) notNil and:[ch isDigit]) ifTrue:[
-        secondNumber := Integer readFrom:aStream onError:-1.
-
-        usFormat ifTrue:[
-            month := firstNumber.
-            day := secondNumber.
-        ] ifFalse:[
-            month := secondNumber.
-            day := firstNumber.
-        ].
+	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.
+	possibeMonthName := aStream throughAnyForWhich:[:ch | ch isLetter].
+	month := Date indexOfMonth:possibeMonthName asLowercase.
+	day := firstNumber.
     ].
 
     (day between:1 and:31) ifFalse:[ TimeConversionError raiseErrorString:' - bad day' ].
@@ -499,46 +482,46 @@
     year := Integer readFrom:aStream onError:[ TimeConversionError raiseErrorString:' - bad year' ].
 
     aStream atEnd ifTrue:[
-        hour := min := sec := millis := 0.
+	hour := min := sec := millis := 0.
     ] ifFalse:[
-        [(ch := aStream peekOrNil) notNil and:[ch isDigit not]] whileTrue:[aStream next].
-        hour := Integer readFrom:aStream onError:-1.
-        (hour between:0 and:24) ifFalse:[ TimeConversionError raiseErrorString:' - bad hour' ].
-
-        [(ch := aStream peekOrNil) notNil and:[ch isDigit not]] whileTrue:[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:[
-            [(ch := aStream peekOrNil) notNil and:[ch isDigit not]] whileTrue:[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.
-            ].  
-            utcOffsetOrNil := self utcOffsetFrom:aStream
-        ].
+	[(ch := aStream peekOrNil) notNil and:[ch isDigit not]] whileTrue:[aStream next].
+	hour := Integer readFrom:aStream onError:-1.
+	(hour between:0 and:24) ifFalse:[ TimeConversionError raiseErrorString:' - bad hour' ].
+
+	[(ch := aStream peekOrNil) notNil and:[ch isDigit not]] whileTrue:[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:[
+	    [(ch := aStream peekOrNil) notNil and:[ch isDigit not]] whileTrue:[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.
+	    ].
+	    utcOffsetOrNil := self utcOffsetFrom:aStream
+	].
     ].
 
     "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' ].
+	(min ~~ 0 or:[sec ~~ 0 or:[millis ~~ 0]]) ifTrue:[ TimeConversionError raiseErrorString:' - bad hour' ].
     ].
     utcOffsetOrNil notNil ifTrue:[
-        utcOffsetOrNil := utcOffsetOrNil negated.
-        utcOffsetOrNil = 0 ifTrue:[
-            "/ utc timestamp
-            ^ UtcTimestamp year:year month:month day:day hour:hour minute:min second:sec millisecond:millis
-        ].
-        ^ ((TZTimestamp year:year month:month day:day hour:hour minute:min second:sec millisecond:millis) utcOffset:utcOffsetOrNil) - utcOffsetOrNil
+	utcOffsetOrNil := utcOffsetOrNil negated.
+	utcOffsetOrNil = 0 ifTrue:[
+	    "/ utc timestamp
+	    ^ UtcTimestamp year:year month:month day:day hour:hour minute:min second:sec millisecond:millis
+	].
+	^ ((TZTimestamp year:year month:month day:day hour:hour minute:min second:sec millisecond:millis) utcOffset:utcOffsetOrNil) - utcOffsetOrNil
     ].
     "/ a local timestamp
     ^ self year:year month:month day:day hour:hour minute:min second:sec millisecond:millis.
@@ -590,8 +573,8 @@
 
     "/ changed to use the new reader
     ^ TimestampISO8601Builder
-        read:aStringOrStream withClass:self
-        yearAlreadyReadAs:yearOrNil
+	read:aStringOrStream withClass:self
+	yearAlreadyReadAs:yearOrNil
 
 "/    |str day month dayInWeek week year hour min sec tmpDay millis fraction isUtcTime peekChar ch|
 "/
@@ -764,9 +747,9 @@
     |retVal|
 
     ConversionError handle:[:ex |
-        retVal := exceptionValue value
+	retVal := exceptionValue value
     ] do:[
-        retVal := self readIso8601FormatFrom:aStringOrStream yearAlreadyRead:yearOrNil
+	retVal := self readIso8601FormatFrom:aStringOrStream yearAlreadyRead:yearOrNil
     ].
     ^ retVal
 ! !
@@ -779,32 +762,32 @@
      On error, exceptionalValue is returned.
      If exceptionalValue is a one-arg block, an error message is passed as argument.
      Format:
-        %h      hours, 00..23 (i.e. european)  0-padded to length 2
-        %u      hours, 00..12 (i.e. us)        0-padded to length 2
-        %m      minutes, 00..59                0-padded to length 2
-        %s      seconds, 00..59                0-padded to length 2
-        %i      milliseconds, 000..999         0-padded to length 3
-        %a      am/pm
-
-        %d             - day
-        %D             - day
-        %(day)         - day
-
-        %m             - month
-        %M             - month
-        %(month)       - month
-
-        %(monthName)   - monthName
-
-        %(year)        - year, full 4 digits
-        %Y             - year, last 2 digits only,
-                         0..71 map to 2000..2071;
-                         72..99 map to 1972..1999;
-        %Y1900          - year, last 2 digits only, map to 1900..1999
-        %Y2000          - year, last 2 digits only, map to 2000..2099
+	%h      hours, 00..23 (i.e. european)  0-padded to length 2
+	%u      hours, 00..12 (i.e. us)        0-padded to length 2
+	%m      minutes, 00..59                0-padded to length 2
+	%s      seconds, 00..59                0-padded to length 2
+	%i      milliseconds, 000..999         0-padded to length 3
+	%a      am/pm
+
+	%d             - day
+	%D             - day
+	%(day)         - day
+
+	%m             - month
+	%M             - month
+	%(month)       - month
+
+	%(monthName)   - monthName
+
+	%(year)        - year, full 4 digits
+	%Y             - year, last 2 digits only,
+			 0..71 map to 2000..2071;
+			 72..99 map to 1972..1999;
+	%Y1900          - year, last 2 digits only, map to 1900..1999
+	%Y2000          - year, last 2 digits only, map to 2000..2099
 
      an optional length after the % gives a field length;
-        i.e. %2h%2m%2s parses 123557 as 12:35:37
+	i.e. %2h%2m%2s parses 123557 as 12:35:37
 
      Please consider using a standard format, such as iso8601.
     "
@@ -815,83 +798,83 @@
      len now s|
 
     error := [:msg |
-                exceptionalValue isBlock ifTrue:[
-                    ^ exceptionalValue valueWithOptionalArgument:'format error; space expcected'
-                ] ifFalse:[
-                    ^ exceptionalValue value
-                ].
-             ].
+		exceptionalValue isBlock ifTrue:[
+		    ^ exceptionalValue valueWithOptionalArgument:'format error; space expcected'
+		] ifFalse:[
+		    ^ exceptionalValue value
+		].
+	     ].
 
     itemHandler := [:format |
-        |input|
-        input := len isNil ifTrue:[ inStream ] ifFalse:[ inStream next: len ].
-
-        ( #('d' 'D' 'day' ) includes:format ) ifTrue:[
-            day := Integer readFrom:input onError:[ error value:'invalid day' ].
-
-        ] ifFalse:[ ( format = 'month' ) ifTrue:[
-            month := Integer readFrom:input onError:[ error value:'invalid month' ].
-
-        ] ifFalse:[ ( format = 'year' or:[ format = 'y' ]) ifTrue:[
-            year := Integer readFrom:input onError:[ error value:'invalid year' ].
-
-        ] ifFalse:[ ( format = 'Y' ) ifTrue:[
-            year := Integer readFrom:input onError:[ error value:'invalid year' ].
-            (year between:0 and: 99) ifFalse:[ error value:'invalid year' ].
-            (year between:0 and:71) ifTrue:[
-                year := year + 1900
-            ] ifFalse:[
-                year := year + 2000
-            ]
-
-        ] ifFalse:[ (format = 'monthName') ifTrue:[
-            s := input nextMatching:[:c | c isLetter] thenMatching:[:c | c isLetter].
-            month := Date indexOfMonth:s asLowercase language:languageOrNil
-
-        ] ifFalse:[ ( format = 'Y1900' ) ifTrue:[
-            year := Integer readFrom:input onError:[ error value:'invalid year' ].
-            (year between:0 and: 99) ifFalse:[ error value:'invalid year' ].
-            year := year + 1900
-
-        ] ifFalse:[ ( format = 'Y2000' ) ifTrue:[
-            year := Integer readFrom:input onError:[ error value:'invalid year' ].
-            (year between:0 and: 99) ifFalse:[ error value:'invalid year' ].
-            year := year + 2000
-
-        ] ifFalse:[ ( format = 'h' or:[ format = 'H' ]) ifTrue:[
-            hour := Integer readFrom:input onError:[ error value:'invalid hour' ].
-
-        ] ifFalse:[ ( format = 'u'  or:[ format = 'U']) ifTrue:[
-            hour := Integer readFrom:input onError:[ error value:'invalid hour' ].
-
-        ] ifFalse:[ ( format = 'm'  or:[ format = 'M' ]) ifTrue:[
-            minute := Integer readFrom:input onError:[ error value:'invalid minute' ].
-
-        ] ifFalse:[ ( format = 's'  or:[ format = 'S' ]) ifTrue:[
-            second := Integer readFrom:input onError:[ error value:'invalid second' ].
-
-        ] ifFalse:[ ( format = 'i'  or:[ format = 'I' ]) ifTrue:[
-            millisecond := Integer readFrom:input onError:[ error value:'invalid month' ].
-
-        ] ifFalse:[ ( format = 'tz' ) ifTrue:[
-            utcOffset := self utcOffsetFrom:input.
-            utcOffset isNil ifTrue:[ error value:'invalid timezone' ]
-        ] ifFalse:[ ( format = 'a' ) ifTrue:[
-            s := (input next:2) asLowercase.
-            s = 'am' ifTrue:[
-                (hour between:0 and:12) ifFalse:[ error value:'invalid hour' ]
-            ] ifFalse:[
-                s = 'pm' ifTrue:[
-                    (hour between:1 and:12) ifFalse:[ error value:'invalid hour' ].
-                    hour := hour + 12.
-                ] ifFalse:[
-                    error value:'invalid am/pm'
-                ]
-            ]
-
-        ] ifFalse:[
-            error value:'unhandled format:',format
-        ]]]]]]]]]]]]]]
+	|input|
+	input := len isNil ifTrue:[ inStream ] ifFalse:[ inStream next: len ].
+
+	( #('d' 'D' 'day' ) includes:format ) ifTrue:[
+	    day := Integer readFrom:input onError:[ error value:'invalid day' ].
+
+	] ifFalse:[ ( format = 'month' ) ifTrue:[
+	    month := Integer readFrom:input onError:[ error value:'invalid month' ].
+
+	] ifFalse:[ ( format = 'year' or:[ format = 'y' ]) ifTrue:[
+	    year := Integer readFrom:input onError:[ error value:'invalid year' ].
+
+	] ifFalse:[ ( format = 'Y' ) ifTrue:[
+	    year := Integer readFrom:input onError:[ error value:'invalid year' ].
+	    (year between:0 and: 99) ifFalse:[ error value:'invalid year' ].
+	    (year between:0 and:71) ifTrue:[
+		year := year + 1900
+	    ] ifFalse:[
+		year := year + 2000
+	    ]
+
+	] ifFalse:[ (format = 'monthName') ifTrue:[
+	    s := input nextMatching:[:c | c isLetter] thenMatching:[:c | c isLetter].
+	    month := Date indexOfMonth:s asLowercase language:languageOrNil
+
+	] ifFalse:[ ( format = 'Y1900' ) ifTrue:[
+	    year := Integer readFrom:input onError:[ error value:'invalid year' ].
+	    (year between:0 and: 99) ifFalse:[ error value:'invalid year' ].
+	    year := year + 1900
+
+	] ifFalse:[ ( format = 'Y2000' ) ifTrue:[
+	    year := Integer readFrom:input onError:[ error value:'invalid year' ].
+	    (year between:0 and: 99) ifFalse:[ error value:'invalid year' ].
+	    year := year + 2000
+
+	] ifFalse:[ ( format = 'h' or:[ format = 'H' ]) ifTrue:[
+	    hour := Integer readFrom:input onError:[ error value:'invalid hour' ].
+
+	] ifFalse:[ ( format = 'u'  or:[ format = 'U']) ifTrue:[
+	    hour := Integer readFrom:input onError:[ error value:'invalid hour' ].
+
+	] ifFalse:[ ( format = 'm'  or:[ format = 'M' ]) ifTrue:[
+	    minute := Integer readFrom:input onError:[ error value:'invalid minute' ].
+
+	] ifFalse:[ ( format = 's'  or:[ format = 'S' ]) ifTrue:[
+	    second := Integer readFrom:input onError:[ error value:'invalid second' ].
+
+	] ifFalse:[ ( format = 'i'  or:[ format = 'I' ]) ifTrue:[
+	    millisecond := Integer readFrom:input onError:[ error value:'invalid month' ].
+
+	] ifFalse:[ ( format = 'tz' ) ifTrue:[
+	    utcOffset := self utcOffsetFrom:input.
+	    utcOffset isNil ifTrue:[ error value:'invalid timezone' ]
+	] ifFalse:[ ( format = 'a' ) ifTrue:[
+	    s := (input next:2) asLowercase.
+	    s = 'am' ifTrue:[
+		(hour between:0 and:12) ifFalse:[ error value:'invalid hour' ]
+	    ] ifFalse:[
+		s = 'pm' ifTrue:[
+		    (hour between:1 and:12) ifFalse:[ error value:'invalid hour' ].
+		    hour := hour + 12.
+		] ifFalse:[
+		    error value:'invalid am/pm'
+		]
+	    ]
+
+	] ifFalse:[
+	    error value:'unhandled format:',format
+	]]]]]]]]]]]]]]
    ].
 
     hour := 0.
@@ -904,41 +887,41 @@
     formatStream := formatString readStream.
 
     [formatStream atEnd] whileFalse:[
-        fChar := formatStream next.
-        fChar = Character space ifTrue:[
-            inStream peek isSeparator ifFalse:[ error value: 'format error; space expcected' ].
-            inStream skipSeparators.
-        ] ifFalse:[
-            fChar == $% ifTrue:[
-                len := nil.
-                (formatStream peek isDigit) ifTrue:[
-                    len := Integer readFrom:formatStream onError:[ error value: 'format error; invalid length' ]
-                ].
-                (formatStream peek == $() ifTrue:[
-                    formatStream next.
-                    format := formatStream upTo:$).
-                ] ifFalse:[
-                    (formatStream peek == ${) ifTrue:[
-                        formatStream next.
-                        format := formatStream upTo:$}.
-                    ] ifFalse:[
-                        (formatStream peek isLetter) ifTrue:[
-                            format := formatStream nextAlphaNumericWord.
-                        ] ifFalse:[
-                            error value:'unhandled format:',formatStream peek
-                        ]
-                    ]
-                ].
-                itemHandler value:format.
-            ] ifFalse:[
-                inStream peek = fChar ifFalse:[^ error value: 'format error; ',fChar,' expcected'].
-                inStream next.
-            ]
-        ].
+	fChar := formatStream next.
+	fChar = Character space ifTrue:[
+	    inStream peek isSeparator ifFalse:[ error value: 'format error; space expcected' ].
+	    inStream skipSeparators.
+	] ifFalse:[
+	    fChar == $% ifTrue:[
+		len := nil.
+		(formatStream peek isDigit) ifTrue:[
+		    len := Integer readFrom:formatStream onError:[ error value: 'format error; invalid length' ]
+		].
+		(formatStream peek == $() ifTrue:[
+		    formatStream next.
+		    format := formatStream upTo:$).
+		] ifFalse:[
+		    (formatStream peek == ${) ifTrue:[
+			formatStream next.
+			format := formatStream upTo:$}.
+		    ] ifFalse:[
+			(formatStream peek isLetter) ifTrue:[
+			    format := formatStream nextAlphaNumericWord.
+			] ifFalse:[
+			    error value:'unhandled format:',formatStream peek
+			]
+		    ]
+		].
+		itemHandler value:format.
+	    ] ifFalse:[
+		inStream peek = fChar ifFalse:[^ error value: 'format error; ',fChar,' expcected'].
+		inStream next.
+	    ]
+	].
     ].
 
     year isNil ifTrue:[
-        year := (now := Timestamp now) year
+	year := (now := Timestamp now) year
     ].
 
     ^ (self year:year month:month day:day hour:(hour ? 0) minute:(minute ? 0) second:(second ? 0) millisecond:millisecond) + utcOffset
@@ -966,9 +949,9 @@
     stream := aStringOrStream readStream.
 
     Error handle:[:ex |
-        newTime := super readFrom:stream onError:exceptionBlock
+	newTime := super readFrom:stream onError:exceptionBlock
     ] do:[
-        newTime := self basicReadFrom:stream.
+	newTime := self basicReadFrom:stream.
     ].
     ^ newTime
 
@@ -993,9 +976,9 @@
 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.
+	yyyymmddHHMMSS.iii+uuuu, which is the ASN1 GeneralizedTime format.
      or:
-        yyyy-mm-dd HH:MM:SS.iii +uuuu.
+	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,
@@ -1008,11 +991,11 @@
     "
 
     ^ self
-        readGeneralizedFrom:aStringOrStream
-        short:false
-        onError:[
-            self conversionErrorSignal raiseErrorString:'Timestamp format error'
-        ].
+	readGeneralizedFrom:aStringOrStream
+	short:false
+	onError:[
+	    self conversionErrorSignal raiseErrorString:'Timestamp format error'
+	].
 
     "Created: / 22-08-2006 / 16:05:55 / cg"
 !
@@ -1020,9 +1003,9 @@
 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.
+	yyyymmddHHMMSS.iii+uuuu, which is the ASN1 GeneralizedTime format.
      or:
-        yyyy-mm-dd HH:MM:SS.iii +uuuu.
+	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,
@@ -1075,13 +1058,13 @@
 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.
+	    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.
+	    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
@@ -1096,75 +1079,75 @@
 
 
     ^ [
-        |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
+	|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.
 
     "
@@ -1225,9 +1208,9 @@
     |retVal|
 
     ConversionError handle:[:ex |
-        retVal := exceptionValue value
+	retVal := exceptionValue value
     ] do:[
-        retVal := TimestampISO8601Builder read:aStringOrStream withClass:self
+	retVal := TimestampISO8601Builder read:aStringOrStream withClass:self
     ].
     ^ retVal
 !
@@ -1287,9 +1270,9 @@
     |retVal|
 
     ConversionError handle:[:ex |
-        retVal := exceptionValue value
+	retVal := exceptionValue value
     ] do:[
-        retVal := TimestampISO8601Builder read:aStringOrStream withClass:self
+	retVal := TimestampISO8601Builder read:aStringOrStream withClass:self
     ].
     ^ retVal
 
@@ -1316,33 +1299,33 @@
      asctime-date   = wkday SP date3 SP time SP 4DIGIT
 
      date1          = 2DIGIT SP month SP 4DIGIT
-                      ; day month year (e.g., 02 Jun 1982)
+		      ; day month year (e.g., 02 Jun 1982)
      date2          = 2DIGIT '-' month '-' 2DIGIT
-                      ; day-month-year (e.g., 02-Jun-82)
+		      ; day-month-year (e.g., 02-Jun-82)
      date3          = month SP ( 2DIGIT | ( SP 1DIGIT ))
-                      ; month day (e.g., Jun  2)
+		      ; month day (e.g., Jun  2)
 
      time           = 2DIGIT ':' 2DIGIT ':' 2DIGIT
-                      ; 00:00:00 - 23:59:59
+		      ; 00:00:00 - 23:59:59
 
      wkday          = 'Mon' | 'Tue' | 'Wed'
-                    | 'Thu' | 'Fri' | 'Sat' | 'Sun'
+		    | 'Thu' | 'Fri' | 'Sat' | 'Sun'
 
      weekday        = 'Monday' | 'Tuesday' | 'Wednesday'
-                    | 'Thursday' | 'Friday' | 'Saturday' | 'Sunday'
+		    | 'Thursday' | 'Friday' | 'Saturday' | 'Sunday'
 
      month          = 'Jan' | 'Feb' | 'Mar' | 'Apr'
-                    | 'May' | 'Jun' | 'Jul' | 'Aug'
-                    | 'Sep' | 'Oct' | 'Nov' | 'Dec'
+		    | 'May' | 'Jun' | 'Jul' | 'Aug'
+		    | 'Sep' | 'Oct' | 'Nov' | 'Dec'
 
      Mon, 17 Aug 2009 11:11:15 GMT
 
      however, occasionally, someone presents us with non-UTC strings which include a timezone;
      thus, this also supports:
-         Mon, 17 Aug 2009 11:11:15 +xxxx
-         Mon, 17 Aug 2009 11:11:15 -xxxx
+	 Mon, 17 Aug 2009 11:11:15 +xxxx
+	 Mon, 17 Aug 2009 11:11:15 -xxxx
      and:
-         Mon, 17 Aug 2009 11:11:15 PST
+	 Mon, 17 Aug 2009 11:11:15 PST
     "
 
     |parts indexModifier utcOffsetString utcOffset day year time monthName month|
@@ -1351,13 +1334,13 @@
 
     parts := rfc1123String subStrings:Character space.
     parts size == 6 ifTrue:[
-        indexModifier := 0.
+	indexModifier := 0.
     ] ifFalse:[
-        parts size == 5 ifTrue:[
-            indexModifier := -1.
-        ] ifFalse:[
-            ^ exceptionBlock value
-        ].
+	parts size == 5 ifTrue:[
+	    indexModifier := -1.
+	] ifFalse:[
+	    ^ exceptionBlock value
+	].
     ].
 
     utcOffsetString := (parts at:6 + indexModifier).
@@ -1369,12 +1352,12 @@
     monthName := parts at:3 + indexModifier.
 
     month := (1 to:12) asOrderedCollection detect:[:i |
-        (Date abbreviatedNameOfMonth:i language:#en) sameAs:monthName
+	(Date abbreviatedNameOfMonth:i language:#en) sameAs:monthName
     ] ifNone:[^ exceptionBlock].
 
     ^ (self
-        fromDate:(Date newDay:day monthIndex:month year:year)
-        andTime:time) + utcOffset
+	fromDate:(Date newDay:day monthIndex:month year:year)
+	andTime:time) + utcOffset
 
     "
      self readRFC1123FormatFrom:'Mon, 17 Aug 2009 11:11:15 PST' onError:nil
@@ -1388,7 +1371,7 @@
 
 timezoneInfo
     "return a table containing timezone information.
-     This may or may not be correct by the time you read this.  
+     This may or may not be correct by the time you read this.
      It is recommended to add explicit information in the form of +hh:mm to a printed
      representation, instead of using names.
 
@@ -1397,151 +1380,151 @@
      the end so they match last."
 
     ^ #(
-            'Z'     0                 "/ zulu
-            'UTC'   0
-            'GMT'   0
-
-            "/ US
-            'HAST'  -10                "/ hawai standard
-            'AKST'   -9                "/ alaska standard
-            'YST'   -9                 "/ yukon standard
-            'PST'   -8                 "/ pacific standard
-            'PT'    -8                 "/ pacific standard
-            'MST'   -7                 "/ mountain standard
-            'CST'   -6                 "/ central standard
-            'EST'   -5                 "/ eastern standard
-            'AST'   -4                 "/ atlantic standard
-
-            'NST'   -3.5               "/ new foundland standard
-            'PMST'  -3                 "/ pierre & miquelon
-            'WGT'   -3                 "/ west greenland     
-            'EGT'   -1                 "/ east greenland      
-
-            "/ europe
-            'CET'   1                 "/ central european
-            'EET'   2                 "/ east european
-            'WET'   0                  "/ west european
-            "/ conflict with india!!
-            "/ 'IST'   1               "/ irish standard time
-            "/ 'IST'   1               "/ israel standard time
-            'AZOT'   -1                "/ azores standard
-
-            'MSK'   4                  "/ moscow european
-            'MSD'   4
-            'BT'    4                  "/ baghdad 
-
-            "/ pacific
-            'NZST' 12                 "/ new zealand standard
-            'FJT' 12                  "/ fiji
-
-            "/ south america
-            'ART'   -3                 "/ argentina
-            'BOT'   -4                 "/ bolivia
-            'BRT'   -3                 "/ brasilia
-            'CLT'   -4                 "/ chile
-            'ECT'   -5                 "/ equador
-            'PET'   -5                 "/ peru
-            'PYT'   -4                 "/ paraguay
-            'UYT'   -3                 "/ uruguay
-            'VET'   -4.5               "/ venezuela standard
-            'VST'   -4.5               "/ venezuela standard
-
-            "/ africa
-            'CAT'   2                 "/ central africa
-            'EAT'   3                 "/ east africa
-            'SAST'  2                 "/ south africa standard
-            'WAT'   1                 "/ west africa
-            'WT'    0                 "/ west sahara standard
-
-            'AST'   3                 "/ arabia
-            'IRT'   3.5                "/ iran time 
-            'AFT'   4.5               "/ afghanistan time 
-
-            'HKT'   8                 "/ hongkong
-            'IST'   5.5               "/ india standard
-            'ICT'   7                 "/ indochina 
-            'CNST'  8                 "/ china standard 
-            'JST'   9                 "/ japan standard
-            'KST'   9                 "/ korea standard
-            'SGT'   8                 "/ singapore
-            'MYT'   8                 "/ malaysia
-            'AWST'  8                 "/ australian west standard
-            'ACWST' 8.75              "/ australian central western standard
-            'ACST'  9.5               "/ australian central standard
-            'AEST'  10                "/ australian east standard
-            'NFT'   11.5              "/ norfolk island, australia
-
-            'CHAST' 12.75             "/ chatham island standard
-            'WST'   13                "/ west samoa - yes thats 13!!
-            'TOT'   13                "/ tonga - yes thats 13!!
-            'TKT'   13                "/ tokelau - yes thats 13!!
-            'LINT'   14               "/ line islands - yes thats 14!!
-
-            "/ misc
-            'IDLW'  -12               "/ international date line west
-            'IDLE'  12                "/ international date line east
-
-            "/ military
-            'A'     1                 "/ alpha
-            'B'     2                 "/ bravo
-            'C'     3                 "/ charlie
-            'D'     4                 "/ delta
-            'E'     5                 "/ echo
-            'F'     6                 "/ foxtrot
-            'G'     7                 "/ golf
-            'H'     8                 "/ hotel
-            'I'     9                 "/ also called india - how misleading
-            'K'     10                "/ kilo
-            'L'     11                "/ lima - but not there
-            'M'     12                "/ mike
-            'N'     -1                "/ november (but also in other months)
-            'O'     -2                "/ oscar
-            'P'     -3                "/ papa (not mama)
-            'Q'     -4                "/ quebec - really?
-            'R'     -5                "/ romeo and juliet
-            'S'     -6                "/ sierra
-            'T'     -7                "/ tango (&rumba)
-            'U'     -8                "/ uniform
-            'V'     -9                "/ victor
-            'W'     -10               "/ whiskey (scotch?)
-            'X'     -11               "/ xray
-            'Y'     -12               "/ yankee
-
-            'MEZ'   1                 "/ central european (german)
-            'MESZ'  2                 "/ central european summer (german)
-            'WESZ'  1                 "/ west european summer (german)
-
-            'WEZ'   0                 "/ west european (german)
-
-            'HADT'  -9                "/ hawaii summer
-            'ADT'   -3
-            'AKDT'  -9                "/ alaska summer
-            'YDT'   -8                "/ yukon summer
-            'PDT'   -7                "/ pacific daylight saving
-            'MDT'   -6                "/ mountain daylight saving
-            'CDT'   -5                "/ central daylight saving      
-            'EDT'   -4                "/ eastern daylight saving        
-            'CLST'  -3                "/ chile summer
-            'NDT'   -2.5
-            'PMDT'  -2
-            'BRST'  -2                "/ brasilia summer
-            'WGST'  -2                "/ west greenland summer
-            'EGST'   0                "/ east greenland summer
-            'AZOST'  0                "/ azores summer
-            'EEST'  3
-            'CEST'  2
-            'WAST'  2                 "/ west africa summer 
-            "/ 'WST'   1                 "/ west sahara summer - conflict with west samoa
-            'WEST'  1
-           'BST'   1                 "/ british summer time
-            'IRST'  4.5               "/ iran summer time 
-            'AWDT'  9                 "/ australian west daylight saving
-            'ACDT'  10.5              "/ australian central daylight saving
-            'AEDT'  11                "/ australian east daylight saving
-            'CHADT'   13.75           "/ chatham island daylight saving
-            'FJST' 13                 "/ fiji summer
-            'NZDT'  13                "/ new zealand summer
-        ).
+	    'Z'     0                 "/ zulu
+	    'UTC'   0
+	    'GMT'   0
+
+	    "/ US
+	    'HAST'  -10                "/ hawai standard
+	    'AKST'   -9                "/ alaska standard
+	    'YST'   -9                 "/ yukon standard
+	    'PST'   -8                 "/ pacific standard
+	    'PT'    -8                 "/ pacific standard
+	    'MST'   -7                 "/ mountain standard
+	    'CST'   -6                 "/ central standard
+	    'EST'   -5                 "/ eastern standard
+	    'AST'   -4                 "/ atlantic standard
+
+	    'NST'   -3.5               "/ new foundland standard
+	    'PMST'  -3                 "/ pierre & miquelon
+	    'WGT'   -3                 "/ west greenland
+	    'EGT'   -1                 "/ east greenland
+
+	    "/ europe
+	    'CET'   1                 "/ central european
+	    'EET'   2                 "/ east european
+	    'WET'   0                  "/ west european
+	    "/ conflict with india!!
+	    "/ 'IST'   1               "/ irish standard time
+	    "/ 'IST'   1               "/ israel standard time
+	    'AZOT'   -1                "/ azores standard
+
+	    'MSK'   4                  "/ moscow european
+	    'MSD'   4
+	    'BT'    4                  "/ baghdad
+
+	    "/ pacific
+	    'NZST' 12                 "/ new zealand standard
+	    'FJT' 12                  "/ fiji
+
+	    "/ south america
+	    'ART'   -3                 "/ argentina
+	    'BOT'   -4                 "/ bolivia
+	    'BRT'   -3                 "/ brasilia
+	    'CLT'   -4                 "/ chile
+	    'ECT'   -5                 "/ equador
+	    'PET'   -5                 "/ peru
+	    'PYT'   -4                 "/ paraguay
+	    'UYT'   -3                 "/ uruguay
+	    'VET'   -4.5               "/ venezuela standard
+	    'VST'   -4.5               "/ venezuela standard
+
+	    "/ africa
+	    'CAT'   2                 "/ central africa
+	    'EAT'   3                 "/ east africa
+	    'SAST'  2                 "/ south africa standard
+	    'WAT'   1                 "/ west africa
+	    'WT'    0                 "/ west sahara standard
+
+	    'AST'   3                 "/ arabia
+	    'IRT'   3.5                "/ iran time
+	    'AFT'   4.5               "/ afghanistan time
+
+	    'HKT'   8                 "/ hongkong
+	    'IST'   5.5               "/ india standard
+	    'ICT'   7                 "/ indochina
+	    'CNST'  8                 "/ china standard
+	    'JST'   9                 "/ japan standard
+	    'KST'   9                 "/ korea standard
+	    'SGT'   8                 "/ singapore
+	    'MYT'   8                 "/ malaysia
+	    'AWST'  8                 "/ australian west standard
+	    'ACWST' 8.75              "/ australian central western standard
+	    'ACST'  9.5               "/ australian central standard
+	    'AEST'  10                "/ australian east standard
+	    'NFT'   11.5              "/ norfolk island, australia
+
+	    'CHAST' 12.75             "/ chatham island standard
+	    'WST'   13                "/ west samoa - yes thats 13!!
+	    'TOT'   13                "/ tonga - yes thats 13!!
+	    'TKT'   13                "/ tokelau - yes thats 13!!
+	    'LINT'   14               "/ line islands - yes thats 14!!
+
+	    "/ misc
+	    'IDLW'  -12               "/ international date line west
+	    'IDLE'  12                "/ international date line east
+
+	    "/ military
+	    'A'     1                 "/ alpha
+	    'B'     2                 "/ bravo
+	    'C'     3                 "/ charlie
+	    'D'     4                 "/ delta
+	    'E'     5                 "/ echo
+	    'F'     6                 "/ foxtrot
+	    'G'     7                 "/ golf
+	    'H'     8                 "/ hotel
+	    'I'     9                 "/ also called india - how misleading
+	    'K'     10                "/ kilo
+	    'L'     11                "/ lima - but not there
+	    'M'     12                "/ mike
+	    'N'     -1                "/ november (but also in other months)
+	    'O'     -2                "/ oscar
+	    'P'     -3                "/ papa (not mama)
+	    'Q'     -4                "/ quebec - really?
+	    'R'     -5                "/ romeo and juliet
+	    'S'     -6                "/ sierra
+	    'T'     -7                "/ tango (&rumba)
+	    'U'     -8                "/ uniform
+	    'V'     -9                "/ victor
+	    'W'     -10               "/ whiskey (scotch?)
+	    'X'     -11               "/ xray
+	    'Y'     -12               "/ yankee
+
+	    'MEZ'   1                 "/ central european (german)
+	    'MESZ'  2                 "/ central european summer (german)
+	    'WESZ'  1                 "/ west european summer (german)
+
+	    'WEZ'   0                 "/ west european (german)
+
+	    'HADT'  -9                "/ hawaii summer
+	    'ADT'   -3
+	    'AKDT'  -9                "/ alaska summer
+	    'YDT'   -8                "/ yukon summer
+	    'PDT'   -7                "/ pacific daylight saving
+	    'MDT'   -6                "/ mountain daylight saving
+	    'CDT'   -5                "/ central daylight saving
+	    'EDT'   -4                "/ eastern daylight saving
+	    'CLST'  -3                "/ chile summer
+	    'NDT'   -2.5
+	    'PMDT'  -2
+	    'BRST'  -2                "/ brasilia summer
+	    'WGST'  -2                "/ west greenland summer
+	    'EGST'   0                "/ east greenland summer
+	    'AZOST'  0                "/ azores summer
+	    'EEST'  3
+	    'CEST'  2
+	    'WAST'  2                 "/ west africa summer
+	    "/ 'WST'   1                 "/ west sahara summer - conflict with west samoa
+	    'WEST'  1
+	   'BST'   1                 "/ british summer time
+	    'IRST'  4.5               "/ iran summer time
+	    'AWDT'  9                 "/ australian west daylight saving
+	    'ACDT'  10.5              "/ australian central daylight saving
+	    'AEDT'  11                "/ australian east daylight saving
+	    'CHADT'   13.75           "/ chatham island daylight saving
+	    'FJST' 13                 "/ fiji summer
+	    'NZDT'  13                "/ new zealand summer
+	).
 !
 
 utcOffsetFrom:aStringOrStream
@@ -1566,32 +1549,32 @@
     stream skipSeparators.
 
     stream peek isLetter ifTrue:[
-        tzName := stream upToElementForWhich:[:ch | ch isLetter not].
-
-        i := table indexOf:tzName.
-        i == 0 ifTrue:[
-            ^ nil
-        ].
-        offset := (table at:i+1) * 60 * 60
+	tzName := stream upToElementForWhich:[:ch | ch isLetter not].
+
+	i := table indexOf:tzName.
+	i == 0 ifTrue:[
+	    ^ nil
+	].
+	offset := (table at:i+1) * 60 * 60
     ] ifFalse:[
-        sign := 1.
-        stream peek == $- ifTrue:[
-            sign := -1.
-            stream next.
-        ] ifFalse:[
-            stream peek == $+ ifTrue:[
-                sign := 1.
-                stream next.
-            ] ifFalse:[
-                stream skipSeparators
-            ]
-        ].
-        offset := ((stream next:2) asNumber * 60 * 60).
-        stream peekOrNil notNil ifTrue:[
-            stream peek == $: ifTrue:[ stream next ].
-            offset := offset + ((stream next:2) asNumber * 60).
-        ].
-        offset := offset * sign
+	sign := 1.
+	stream peek == $- ifTrue:[
+	    sign := -1.
+	    stream next.
+	] ifFalse:[
+	    stream peek == $+ ifTrue:[
+		sign := 1.
+		stream next.
+	    ] ifFalse:[
+		stream skipSeparators
+	    ]
+	].
+	offset := ((stream next:2) asNumber * 60 * 60).
+	stream peekOrNil notNil ifTrue:[
+	    stream peek == $: ifTrue:[ stream next ].
+	    offset := offset + ((stream next:2) asNumber * 60).
+	].
+	offset := offset * sign
     ].
 
     "/ return what would be an utcOffset (not what is at the end of an iso string)
@@ -1600,8 +1583,8 @@
     "
      self utcOffsetFrom:'UTC'
      self utcOffsetFrom:'PST'
-     self utcOffsetFrom:'EST'  
-     self utcOffsetFrom:'CET'  
+     self utcOffsetFrom:'EST'
+     self utcOffsetFrom:'CET'
      self utcOffsetFrom:'+0130'
      self utcOffsetFrom:'+01:30'
      self utcOffsetFrom:'+01'
@@ -1616,8 +1599,8 @@
     ^ self utcOffsetFrom:aString
 
     "
-     self utcOffsetFromString:'UTC'  
-     self utcOffsetFromString:'+01'  
+     self utcOffsetFromString:'UTC'
+     self utcOffsetFromString:'+01'
     "
 ! !
 
@@ -1680,7 +1663,7 @@
 
 dayOfWeek
     "return the week-day of the receiver - 1 is sunday, 7 for saturday.
-     WARNING: different from dayInWeek (which returns 1 for monday, ... 7 for sunday).  
+     WARNING: different from dayInWeek (which returns 1 for monday, ... 7 for sunday).
     "
 
     ^ self asDate dayOfWeek
@@ -1718,8 +1701,8 @@
 hours
     "return the hours (0..23)"
 
-    ((osTime < 0) or:[osTime > EpochEndOSTime]) ifTrue:[
-        ^ self asTime hours.
+    (osTime between:MinOSTime and:MaxOSTime) ifFalse:[
+	^ self asTime hours.
     ].
     ^ self timeInfo hours
 
@@ -1767,8 +1750,8 @@
 minutes
     "return the minutes (0..59)"
 
-    ((osTime < 0) or:[osTime > EpochEndOSTime]) ifTrue:[
-        ^ self asTime minutes.
+    (osTime between:MinOSTime and:MaxOSTime) ifFalse:[
+	^ self asTime minutes.
     ].
     ^ self timeInfo minutes
 
@@ -1783,8 +1766,8 @@
     "return the month of the receiver (1..12).
      For compatibility, use instances of Date for this."
 
-    ((osTime < 0) or:[osTime > EpochEndOSTime]) ifTrue:[
-        ^ self asDate month.
+    (osTime between:MinOSTime and:MaxOSTime) ifFalse:[
+	^ self asDate month.
     ].
     ^ self timeInfo month
 
@@ -1821,8 +1804,8 @@
 seconds
     "return the seconds (0..59)"
 
-    ((osTime < 0) or:[osTime > EpochEndOSTime]) ifTrue:[
-        ^ self asTime seconds.
+    (osTime between:MinOSTime and:MaxOSTime) ifFalse:[
+	^ self asTime seconds.
     ].
     ^ self timeInfo seconds
 
@@ -1860,23 +1843,23 @@
 
     best := nil.
     self class timezoneInfo pairWiseDo:[:name :offsetInHours |
-        |thisUtcOffset|
-
-        thisUtcOffset := offsetInHours * 60 * 60.
-        thisUtcOffset == myUtcOffset ifTrue:[^ name ].
+	|thisUtcOffset|
+
+	thisUtcOffset := offsetInHours * 60 * 60.
+	thisUtcOffset == myUtcOffset ifTrue:[^ name ].
     ].
     ^ ((self utcOffset > 0) ifTrue:['+'] ifFalse:['-'])
       , ((myUtcOffset abs // 60) printStringLeftPaddedTo:2 with:$0)
       , ((myUtcOffset abs \\ 60) printStringLeftPaddedTo:2 with:$0)
 
     "
-     Timestamp now timeZoneName     
-     UtcTimestamp now timeZoneName  
-
-     (Timestamp now asTZTimestampInZone:'EST') timeZoneName  
-     (Timestamp now asTZTimestampInZone:'IDLE') timeZoneName  
-     (Timestamp now asTZTimestampInZone:'BRST') timeZoneName  
-     (Timestamp now asTZTimestampInZone:'MYT') timeZoneName  
+     Timestamp now timeZoneName
+     UtcTimestamp now timeZoneName
+
+     (Timestamp now asTZTimestampInZone:'EST') timeZoneName
+     (Timestamp now asTZTimestampInZone:'IDLE') timeZoneName
+     (Timestamp now asTZTimestampInZone:'BRST') timeZoneName
+     (Timestamp now asTZTimestampInZone:'MYT') timeZoneName
     "
 !
 
@@ -1902,9 +1885,9 @@
 !
 
 utcTimeInfo
-    ((osTime < 0) or:[osTime > EpochEndOSTime]) ifTrue:[
-        "/ fake an info which the OS cannot give me
-        ^ self computeUtcTimeInfo
+    (osTime between:MinOSTime and:MaxOSTime) ifFalse:[
+	"/ fake an info which the OS cannot give me
+	^ self computeUtcTimeInfo
     ].
 
     ^ OperatingSystem computeUTCTimeAndDateFrom:osTime
@@ -1931,13 +1914,13 @@
     ^ self asDate weekday
 
     "
-     Timestamp now weekday                              
+     Timestamp now weekday
 
      but maybe a different day there, in the south pacific:
-     (Timestamp now asTZTimestampInZone:'LINT') weekday   
+     (Timestamp now asTZTimestampInZone:'LINT') weekday
 
      but maybe a different day there, in alaska:
-     (Timestamp now asTZTimestampInZone:'AKST') weekday 
+     (Timestamp now asTZTimestampInZone:'AKST') weekday
     "
 !
 
@@ -1945,8 +1928,8 @@
     "return the year of the receiver i.e. 1992.
      For compatibility, use instances of Date for this."
 
-    ((osTime < 0) or:[osTime > EpochEndOSTime]) ifTrue:[
-        ^ self asDate year.
+    (osTime between:MinOSTime and:MaxOSTime) ifFalse:[
+	^ self asDate year.
     ].
     ^ self timeInfo year
 
@@ -1997,7 +1980,7 @@
 millisecondDeltaFrom:aTimestamp
     "return the delta in milliseconds between 2 absolute times.
      The argument is supposed to be BEFORE the receiver,
-        computes self - aTimestamp"
+	computes self - aTimestamp"
 
     ^ self getMilliseconds - (aTimestamp getMilliseconds)
 
@@ -2035,7 +2018,7 @@
 secondDeltaFrom:aTimestamp
     "return the delta in seconds between 2 absolute times.
      The argument is supposed to be BEFORE the receiver,
-        computes self - aTimestamp"
+	computes self - aTimestamp"
 
     ^ self getSeconds - (aTimestamp getSeconds)
 
@@ -2089,14 +2072,14 @@
      Notice: if you convert a local timestamp, you will get the local date;
      otherwise if you convert an utcTimestamp, you'll get the utc date."
 
-    ((osTime < 0) or:[osTime > EpochEndOSTime]) ifTrue:[
-        |secondDelta dayDelta day0 time0 day time|
-
-        secondDelta := osTime // 1000.
-        secondDelta := secondDelta - self utcOffset.
-        dayDelta := secondDelta // (24 * 3600).
-        day0 := self class epoch asDate.
-        ^ day0 addDays:dayDelta.
+    (osTime between:MinOSTime and:MaxOSTime) ifFalse:[
+	|secondDelta dayDelta day0 time0 day time|
+
+	secondDelta := osTime // 1000.
+	secondDelta := secondDelta - self utcOffset.
+	dayDelta := secondDelta // (24 * 3600).
+	day0 := self class epoch asDate.
+	^ day0 addDays:dayDelta.
     ].
     ^ self timeInfo asDate
 
@@ -2154,9 +2137,9 @@
     ^ self asTZTimestamp:self utcOffset
 
     "see the different printStrings of:
-         Timestamp now              
+	 Timestamp now
      and
-         Timestamp now asTZTimestamp
+	 Timestamp now asTZTimestamp
     "
 !
 
@@ -2167,12 +2150,12 @@
     ^ (TZTimestamp fromOSTime:osTime) utcOffset:utcOffset
 
     "what is the time now in NewYork?
-     Timestamp now asTZTimestamp:(Timestamp utcOffsetFrom:'EST') 
-     Timestamp now asTZTimestampInZone:'EST' 
+     Timestamp now asTZTimestamp:(Timestamp utcOffsetFrom:'EST')
+     Timestamp now asTZTimestampInZone:'EST'
 
      what is the time now in Stuttgart?
-     Timestamp now asTZTimestamp:(Timestamp utcOffsetFrom:'MEZ')  
-     Timestamp now asTZTimestampInZone:'MEZ' 
+     Timestamp now asTZTimestamp:(Timestamp utcOffsetFrom:'MEZ')
+     Timestamp now asTZTimestampInZone:'MEZ'
     "
 !
 
@@ -2184,10 +2167,10 @@
     ^ self asTZTimestamp:(Timestamp utcOffsetFrom:timeZoneName)
 
     "what is the time now in NewYork?
-     Timestamp now asTZTimestampInZone:'EST' 
+     Timestamp now asTZTimestampInZone:'EST'
 
      what is the time now in Stuttgart?
-     Timestamp now asTZTimestampInZone:'MEZ'  
+     Timestamp now asTZTimestampInZone:'MEZ'
     "
 !
 
@@ -2198,10 +2181,10 @@
 
     |secondDelta|
 
-    ((osTime < 0) or:[osTime > EpochEndOSTime]) ifTrue:[
-        secondDelta := osTime // 1000.
-        secondDelta := secondDelta - self utcOffset.
-        ^ self class epoch asTime addSeconds:secondDelta.
+    (osTime between:MinOSTime and:MaxOSTime) ifFalse:[
+	secondDelta := osTime // 1000.
+	secondDelta := secondDelta - self utcOffset.
+	^ self class epoch asTime addSeconds:secondDelta.
     ].
     ^ self timeInfo asTime
 
@@ -2215,6 +2198,30 @@
     "
 !
 
+asTimeWithMilliseconds
+    "return a Time object from the receiver.
+     The returned time will only represent the timeOfDay - not the day,
+     it will include the milliseconds."
+
+    |milliSecondDelta|
+
+    (osTime between:MinOSTime and:MaxOSTime) ifFalse:[
+	milliSecondDelta := osTime - (self utcOffset * 1000).
+	^ self class epoch asTime addMilliseconds:milliSecondDelta.
+    ].
+    ^ self timeInfo asTime
+
+    "
+     Timestamp now
+     Timestamp now asTime
+     UtcTimestamp now asTime
+     (Timestamp now addTime:3600) asTime
+     (Timestamp year:2014 month:7 day:1 hour:12 minute:0 second:0) asTime
+     (UtcTimestamp year:2014 month:7 day:1 hour:12 minute:0 second:0) asTime
+    "
+!
+
+
 asTimestamp
     "return an Timestamp object from the receiver - that's the receiver."
 
@@ -2237,7 +2244,7 @@
     "encode myself as an array, from which a copy of the receiver
      can be reconstructed with #decodeAsLiteralArray.
      The encoding is:
-        (#Timestamp YYYYMMDDhhmmss.iii)
+	(#Timestamp YYYYMMDDhhmmss.iii)
     "
 
     |s|
@@ -2246,14 +2253,14 @@
     self printGeneralizedOn:s isLocal:false.
 
     ^ Array
-        with:self class name
-        with:s contents
+	with:self class name
+	with:s contents
 
     "
       Timestamp now literalArrayEncoding
-        decodeAsLiteralArray
+	decodeAsLiteralArray
       UtcTimestamp now literalArrayEncoding
-        decodeAsLiteralArray      
+	decodeAsLiteralArray
     "
 !
 
@@ -2262,8 +2269,8 @@
 
 "
     secondsBetween1901and1970 :=
-        ((Date day:1 month:1 year:1970) subtractDate:(Date day:1 month:1 year:1901))
-        *  (24 * 60 * 60)
+	((Date day:1 month:1 year:1970) subtractDate:(Date day:1 month:1 year:1901))
+	*  (24 * 60 * 60)
 "
 
     ^ self utcSecondsSince1970 + 2177452800.
@@ -2277,8 +2284,7 @@
 
 UTCyear:y month:m day:d hour:h minute:min second:s millisecond:millis
     "private: ask the operating system to compute the internal osTime (based on the epoch),
-     given y,m,d and h,m,s in my time.
-     If that fails (because the timestamp is outside the epoch, compute it manually"
+     given y,m,d and h,m,s in my time."
 
     self setOSTimeFromUTCYear:y month:m day:d hour:h minute:min second:s millisecond:millis
 !
@@ -2288,56 +2294,55 @@
      given y,m,d and h,m,s in local time"
 
     Error handle:[:ex |
-        "handler for timestamps before the epoch or after the OS representable time (2038 on current Unices).
-         Then, an out-of-os-range osTime is generated here manually."
-
-        |deltaDays|
-
-        deltaDays := self class epoch asDate subtractDate:(Date newDay:d month:m year:y).
-        "/ deltadays will be negative for dates before the epoch and positive if after.
-
-        osTime := (h * 3600) + (min * 60) + s.
-        osTime := osTime - (deltaDays * 24 * 3600).
-        osTime := osTime * 1000.
-        osTime := osTime + millis.
+	"handler for timestamps before the epoch or after the OS representable time (2038 on current Unices).
+	 Then, an out-of-os-range osTime is generated here manually."
+
+	|deltaDays|
+
+	deltaDays := self class epoch asDate subtractDate:(Date newDay:d month:m year:y).
+	"/ deltadays will be negative for dates before the epoch and positive if after.
+
+	osTime := (h * 3600) + (min * 60) + s.
+	osTime := osTime - (deltaDays * 24 * 3600).
+	osTime := osTime * 1000.
+	osTime := osTime + millis.
     ] do:[
-        osTime := OperatingSystem
-                computeOSTimeFromUTCYear:y month:m day:d
-                hour:h minute:min second:s
-                millisecond:millis
+	osTime := OperatingSystem
+		computeOSTimeFromUTCYear:y month:m day:d
+		hour:h minute:min second:s
+		millisecond:millis
     ]
 !
 
 setOSTimeFromYear:y month:m day:d hour:h minute:min second:s millisecond:millis
     "private: ask the operating system to compute the internal osTime (based on the epoch),
-     given y,m,d and h,m,s in local time"
+     given y,m,d and h,m,s in local time. If the OS cannot do it, do it here."
 
     Error handle:[:ex |
-        "handler for timestamps before the epoch or after the OS representable time (2038 on current Unices).
-         Then, an out-of-os-range osTime is generated here manually."
-
-        |deltaDays|
-
-        deltaDays := self class epoch asDate subtractDate:(Date newDay:d month:m year:y).
-        "/ deltadays will be negative for dates before the epoch and positive if after.
-
-        osTime := (h * 3600) + (min * 60) + s.
-        osTime := osTime + self utcOffset.
-        osTime := osTime - (deltaDays * 24 * 3600).
-        osTime := osTime * 1000.
-        osTime := osTime + millis.
+	"handler for timestamps before the epoch or after the OS representable time (2038 on current Unices).
+	 Then, an out-of-os-range osTime is generated here manually."
+
+	|deltaDays|
+
+	deltaDays := self class epoch asDate subtractDate:(Date newDay:d month:m year:y).
+	"/ deltadays will be negative for dates before the epoch and positive if after.
+
+	osTime := (h * 3600) + (min * 60) + s.
+	osTime := osTime + self utcOffset.
+	osTime := osTime - (deltaDays * 24 * 3600).
+	osTime := osTime * 1000.
+	osTime := osTime + millis.
     ] do:[
-        osTime := OperatingSystem
-                computeOSTimeFromYear: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 second:s
+		millisecond:millis
     ]
 !
 
 year:y month:m day:d hour:h minute:min second:s millisecond:millis
     "private: ask the operating system to compute the internal osTime (based on the epoch),
-     given y,m,d and h,m,s in my time.
-     If that fails (because the timestamp is outside the epoch, compute it manually"
+     given y,m,d and h,m,s in my time."
 
     self setOSTimeFromYear:y month:m day:d hour:h minute:min second:s millisecond:millis
 ! !
@@ -2356,11 +2361,11 @@
     super addPrintBindingsTo:dict language:languageOrNil.
 
     date year == Date today year ifTrue:[
-        dict at:#yearOrTime put:('%h:%m' expandPlaceholdersWith:dict).
+	dict at:#yearOrTime put:('%h:%m' expandPlaceholdersWith:dict).
     ].
 
     "
-        Timestamp now addPrintBindingsTo:Dictionary new inspect language:nil
+	Timestamp now addPrintBindingsTo:Dictionary new inspect language:nil
     "
 !
 
@@ -2393,8 +2398,8 @@
 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'
+	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.
@@ -2405,16 +2410,16 @@
     |t off|
 
     isLocal ifTrue:[
-        t := self timeInfo.
+	t := self timeInfo.
     ] ifFalse:[
-        t := self asUtcTimestamp timeInfo.
+	t := self asUtcTimestamp timeInfo.
     ].
 
     shortFormat ifTrue:[
-        self assert:(t year between:1951 and:2049).
-        (t year \\ 100) printOn:aStream leftPaddedTo:2 with:$0.
+	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 year    printOn:aStream leftPaddedTo:4 with:$0.
     ].
     t month   printOn:aStream leftPaddedTo:2 with:$0.
     t day     printOn:aStream leftPaddedTo:2 with:$0.
@@ -2425,22 +2430,22 @@
     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.
-        ].
+	"/ 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.
+	].
     ].
 
     "
@@ -2512,9 +2517,9 @@
 printIso8601FormatOn:aStream
     "append the iso8601 representation of the receiver to aStream.
      This format looks like:
-        1999-01-01T24:00:00
+	1999-01-01T24:00:00
      or, for zero hr:min:sec,
-        1999-01-01
+	1999-01-01
      Of course, a 24 hour clock is used.
 
      Timezone information (eg. Z or +0100) is added, so the reader will read as local time."
@@ -2522,20 +2527,20 @@
     |asUTC asLocal|
 
     self isUtcTimestamp ifTrue:[
-        asUTC := true. asLocal := false.
+	asUTC := true. asLocal := false.
     ] ifFalse:[
-        self isLocalTimestamp ifTrue:[
-            asUTC := false. asLocal := false.
-        ] ifFalse:[
-            asUTC := false. asLocal := false.
-        ]
+	self isLocalTimestamp ifTrue:[
+	    asUTC := false. asLocal := false.
+	] ifFalse:[
+	    asUTC := false. asLocal := false.
+	]
     ].
 
     Timestamp::TimestampISO8601Builder
-        print:self compact:false 
-        asLocal:asLocal asUTC:asUTC withMilliseconds:true 
-        timeSeparator:$T 
-        on:aStream
+	print:self compact:false
+	asLocal:asLocal asUTC:asUTC withMilliseconds:true
+	timeSeparator:$T
+	on:aStream
 
 "/
 "/    |format|
@@ -2576,20 +2581,20 @@
     |asUTC asLocal|
 
     self isUtcTimestamp ifTrue:[
-        asUTC := true. asLocal := false.
+	asUTC := true. asLocal := false.
     ] ifFalse:[
-        self isLocalTimestamp ifTrue:[
-            asUTC := false. asLocal := true.
-        ] ifFalse:[
-            asUTC := false. asLocal := false.
-        ]
+	self isLocalTimestamp ifTrue:[
+	    asUTC := false. asLocal := true.
+	] ifFalse:[
+	    asUTC := false. asLocal := false.
+	]
     ].
 
     Timestamp::TimestampISO8601Builder
-        print:self compact:false 
-        asLocal:asLocal asUTC:asUTC withMilliseconds:true 
-        timeSeparator:(Character space) 
-        on:aStream
+	print:self compact:false
+	asLocal:asLocal asUTC:asUTC withMilliseconds:true
+	timeSeparator:(Character space)
+	on:aStream
 
 "/    self printOn:aStream format:'%(year)-%(mon)-%(day) %h:%m:%s.%i'
 "/    self printOn:aStream format:'%(Day)-%(mon)-%(year) %h:%m:%s.%i'
@@ -2624,7 +2629,7 @@
 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'
+	'Fri, 04 Jul 2003 15:56:11 GMT'
      (always GMT and all names in english)"
 
 "/       HTTP-date      = rfc1123-date | rfc850-date | asctime-date
@@ -2658,7 +2663,7 @@
     timeInfo := self asUtcTimestamp timeInfo.
 
     aStream nextPutAll:(#('Mon' 'Tue' 'Wed' 'Thu' 'Fri' 'Sat' 'Sun') at:timeInfo dayInWeek);
-            nextPutAll:', '.
+	    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).
@@ -2677,7 +2682,7 @@
     aStream nextPutAll:' GMT'.
 
     "
-     String streamContents:[:s| Timestamp now printRFC1123FormatOn:s] 
+     String streamContents:[:s| Timestamp now printRFC1123FormatOn:s]
     "
 !
 
@@ -2708,9 +2713,9 @@
 printStringIso8601Format
     "return the Iso8601 representation of the receiver with local timezon information.
      This format looks like:
-        1999-01-01T24:00:00
+	1999-01-01T24:00:00
      or, for zero hr:min:sec,
-        1999-01-01
+	1999-01-01
      Of course, a 24 hour clock is used."
 
     ^ String streamContents:[:s | self printIso8601FormatOn:s]
@@ -2723,7 +2728,7 @@
 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'
+	'Fri, 04 Jul 2003 15:56:11 GMT'
      (always GMT)"
 
     ^ String streamContents:[:s | self printRFC1123FormatOn:s]
@@ -2739,8 +2744,8 @@
      Use a OS/architecture independent format"
 
     aStream nextPut:$(;
-            nextPutAll:self class name;
-            nextPutAll:' readIso8601FormatFrom:'''.
+	    nextPutAll:self class name;
+	    nextPutAll:' readIso8601FormatFrom:'''.
     self printIso8601FormatOn:aStream.
     aStream nextPutAll:''')'.
 
@@ -2761,9 +2766,9 @@
     d := self asDate.
     t := self asTime.
     info := OperatingSystem timeInfoClass new.
-    info year:d year month:d month day:d day 
-         hours:t hours minutes:t minutes seconds:t seconds milliseconds:t milliseconds
-         utcOffset:(self utcOffset) dst:false dayInYear:d dayInYear dayInWeek:d dayInWeek.
+    info year:d year month:d month day:d day
+	 hours:t hours minutes:t minutes seconds:t seconds milliseconds:t milliseconds
+	 utcOffset:(self utcOffset) dst:false dayInYear:d dayInYear dayInWeek:d dayInWeek.
     ^ info
 !
 
@@ -2774,9 +2779,9 @@
     d := self asUtcTimestamp asDate.
     t := self asUtcTimestamp asTime.
     info := OperatingSystem timeInfoClass new.
-    info year:d year month:d month day:d day 
-         hours:t hours minutes:t minutes seconds:t seconds milliseconds:t milliseconds
-         utcOffset:0 dst:false dayInYear:d dayInYear dayInWeek:d dayInWeek.
+    info year:d year month:d month day:d day
+	 hours:t hours minutes:t minutes seconds:t seconds milliseconds:t milliseconds
+	 utcOffset:0 dst:false dayInYear:d dayInYear dayInWeek:d dayInWeek.
     ^ info
 !
 
@@ -2798,7 +2803,7 @@
 getMilliseconds
     "strictly private: return the milliseconds (since the epoch) in utc"
 
-    ^ osTime - OperatingSystem osTimeOf19700101
+    ^ osTime
 
     "Created: 1.7.1996 / 14:33:56 / cg"
 !
@@ -2806,13 +2811,13 @@
 getSeconds
     "strictly private: return the seconds (since the epoch) in utc"
 
-    ^ (osTime - OperatingSystem osTimeOf19700101) // 1000
+    ^ osTime // 1000
 !
 
 setMilliseconds:millis
     "strictly private: set the milliseconds (since the epoch)"
 
-    osTime := OperatingSystem osTimeOf19700101 + millis.
+    osTime := millis.
 
     "Modified: 20.12.1995 / 11:46:36 / stefan"
     "Created: 1.7.1996 / 14:34:24 / cg"
@@ -2821,16 +2826,16 @@
 setSeconds:secs
     "strictly private: set the seconds (since whatever)"
 
-    osTime := OperatingSystem osTimeOf19700101 + (secs * 1000).
+    osTime := (secs * 1000).
 
     "Modified: 20.12.1995 / 11:46:36 / stefan"
     "Modified: 1.7.1996 / 14:34:10 / cg"
 !
 
 timeInfo
-    ((osTime < 0) or:[osTime > EpochEndOSTime]) ifTrue:[
-        "/ fake an info which the OS cannot give me
-        ^ self computeTimeInfo
+    (osTime between:MinOSTime and:MaxOSTime) ifFalse:[
+	"/ fake an info which the OS cannot give me
+	^ self computeTimeInfo
     ].
 
     ^ OperatingSystem computeTimeAndDateFrom:osTime
@@ -2899,15 +2904,15 @@
     utcOffset := (((hours * 60) + minutes) * 60).
 
     minutes isZero ifFalse: [
-        minute := minute + minutes.
-        minute >= 60 ifTrue: [
-            hours := hours + 1.
-            minute := minute - 60.
-        ].
-        minute < 0 ifTrue: [
-            hours := hours - 1.
-            minute := minute + 60.
-        ]
+	minute := minute + minutes.
+	minute >= 60 ifTrue: [
+	    hours := hours + 1.
+	    minute := minute - 60.
+	].
+	minute < 0 ifTrue: [
+	    hours := hours - 1.
+	    minute := minute + 60.
+	]
     ].
 
     "Hours may get zero by time zone specification or by minutes modifications above."
@@ -2916,24 +2921,24 @@
     "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
-        ]
+	"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
-        ]
+	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"
@@ -2946,8 +2951,8 @@
     |monthAndDay|
 
     (dayInYear between: 1 and: 365) ifFalse: [
-        (dayInYear = 366 and:[self leapYear: year])
-            ifFalse: [self malformed: 'Bad day number: ' , dayInYear printString]
+	(dayInYear = 366 and:[self leapYear: year])
+	    ifFalse: [self malformed: 'Bad day number: ' , dayInYear printString]
     ].
 
     monthAndDay := Date monthAndDayFromDayInYear:dayInYear forYear:year.
@@ -2987,8 +2992,8 @@
     "Answer the number of the last day of the given month in the current year."
 
     ^ anInteger = 2
-        ifTrue: [(self leapYear: year) ifTrue: [29] ifFalse: [28]]
-        ifFalse: [#(31 28 31 30 31 30 31 31 30 31 30 31) at: month]
+	ifTrue: [(self leapYear: 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"
 !
@@ -3005,29 +3010,29 @@
      - On UNIX, timestamps can only hold dates between 1970-01-01T00:00:00Z and 2038-01-19T00:00:00Z"
 
     (timestampClass == UtcTimestamp) ifTrue:[
-        ^ UtcTimestamp
-            UTCYear: year month: month day: day
-            hour: hour minute: minute second: second millisecond: millisecond
+	^ UtcTimestamp
+	    UTCYear: year month: month day: day
+	    hour: hour minute: minute second: second millisecond: millisecond
     ].
     (timestampClass == TZTimestamp) ifTrue:[
-        ^ (TZTimestamp
-            UTCYear: year month: month day: day
-            hour: hour minute: minute second: second millisecond: millisecond) utcOffset:utcOffset
+	^ (TZTimestamp
+	    UTCYear: year month: month day: day
+	    hour: hour minute: minute second: second millisecond: millisecond) utcOffset:utcOffset
     ].
 
     (isUtcTime or:[hasTimezone and:[utcOffset == 0]]) ifTrue:[
-        ^ ((timestampClass == Timestamp) ifTrue:UtcTimestamp ifFalse:timestampClass)
-            UTCYear: year month: month day: day
-            hour: hour minute: minute second: second millisecond: millisecond
+	^ ((timestampClass == Timestamp) ifTrue:UtcTimestamp ifFalse:timestampClass)
+	    UTCYear: year month: month day: day
+	    hour: hour minute: minute second: second millisecond: millisecond
     ] ifFalse:[
-        hasTimezone ifTrue:[
-            ^ (((timestampClass == Timestamp) ifTrue:TZTimestamp ifFalse:timestampClass)
-                UTCYear: year month: month day: day
-                hour: hour minute: minute second: second millisecond: millisecond) utcOffset:utcOffset
-        ].
-        ^ timestampClass
-            year: year month: month day: day
-            hour: hour minute: minute second: second millisecond: millisecond
+	hasTimezone ifTrue:[
+	    ^ (((timestampClass == Timestamp) ifTrue:TZTimestamp ifFalse:timestampClass)
+		UTCYear: year month: month day: day
+		hour: hour minute: minute second: second millisecond: millisecond) utcOffset:utcOffset
+	].
+	^ timestampClass
+	    year: year month: month day: day
+	    hour: hour minute: minute second: second millisecond: millisecond
     ]
 
     "Created: / 15-06-2005 / 15:39:24 / masca"
@@ -3060,21 +3065,21 @@
     For an example of what the builder can read, see the examples method and ISO 8601 itself.
 
     [author:]
-        Martin Dvorak (masca@volny.cz)
+	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.
+	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
+	Timestamp
 "
 !
 
@@ -3084,9 +3089,9 @@
     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)
+	Timestamp readISO8601From: (TimestampISO8601Builder print: Timestamp now)
+	UtcTimestamp readISO8601From: (TimestampISO8601Builder print: UtcTimestamp now)
+	Timestamp readISO8601From: (TimestampISO8601Builder print: UtcTimestamp now)
 
     Timestamp readISO8601From:'fooBar' onError:[ Timestamp now ].
 "
@@ -3152,7 +3157,7 @@
     self print:aTimestamp compact:false asLocal:true asUTC:false withMilliseconds:true on:aStream
 
     "
-     self printAsLocalTime:(Timestamp now) on:Transcript    
+     self printAsLocalTime:(Timestamp now) on:Transcript
     "
 !
 
@@ -3219,25 +3224,25 @@
 
     tzOffset := tzOffsetArg.
     tzOffset ~= 0 ifTrue:[
-        tzOffset := tzOffset // 60.     "/ convert from seconds to minutes
-        tzOffset < 0 ifTrue:[
-            tzOffset := tzOffset negated.
-            aStream nextPut:$+
-        ] ifFalse:[
-            aStream nextPut:$-.
-        ].
-
-        tzHours := tzOffset // 60.
-        tzMinutes := tzOffset \\ 60.
-        (tzHours ~= 0 or:[tzMinutes ~= 0]) ifTrue:[
-            aStream
-                nextPutAll:(tzHours printStringRadix: 10 size: 2 fill: $0).
-            tzMinutes ~= 0 ifTrue:[
-                aStream
-                    nextPut: $:;
-                    nextPutAll: (tzMinutes printStringRadix: 10 size: 2 fill: $0).
-            ].
-        ].
+	tzOffset := tzOffset // 60.     "/ convert from seconds to minutes
+	tzOffset < 0 ifTrue:[
+	    tzOffset := tzOffset negated.
+	    aStream nextPut:$+
+	] ifFalse:[
+	    aStream nextPut:$-.
+	].
+
+	tzHours := tzOffset // 60.
+	tzMinutes := tzOffset \\ 60.
+	(tzHours ~= 0 or:[tzMinutes ~= 0]) ifTrue:[
+	    aStream
+		nextPutAll:(tzHours printStringRadix: 10 size: 2 fill: $0).
+	    tzMinutes ~= 0 ifTrue:[
+		aStream
+		    nextPut: $:;
+		    nextPutAll: (tzMinutes printStringRadix: 10 size: 2 fill: $0).
+	    ].
+	].
     ].
 
     "
@@ -3260,22 +3265,22 @@
 print: aTimestamp compact:compact asLocal:asLocal asUTC:asUTC withMilliseconds:withMillis on: aStream
     "Print the given timestamp in general ISO8601 format,
      such as '2014-11-06T11:48:09Z'.
-        compact: if true, the compact format (without separating dashes and colons is generated)
-        asLocal: if true, generates a localtime string (with the machine's current timezone setting)
-        asUTC: if true, generates a utc string 
-            if both are false:
-                generate a string depending on the type of timestamp:
-                    if local: generate a local timezone string
-                    if utc: generate a utc string
-                    otherwise it is a timestamp from another timezone (TZTimestamp), then print in its timezone
-        withMilliseconds: if false, no milliseconds are generated"
-
-    self 
-        print:aTimestamp 
-        compact:compact asLocal:asLocal asUTC:asUTC 
-        withMilliseconds:withMillis 
-        timeSeparator:$T 
-        on:aStream
+	compact: if true, the compact format (without separating dashes and colons is generated)
+	asLocal: if true, generates a localtime string (with the machine's current timezone setting)
+	asUTC: if true, generates a utc string
+	    if both are false:
+		generate a string depending on the type of timestamp:
+		    if local: generate a local timezone string
+		    if utc: generate a utc string
+		    otherwise it is a timestamp from another timezone (TZTimestamp), then print in its timezone
+	withMilliseconds: if false, no milliseconds are generated"
+
+    self
+	print:aTimestamp
+	compact:compact asLocal:asLocal asUTC:asUTC
+	withMilliseconds:withMillis
+	timeSeparator:$T
+	on:aStream
 
     "
      self print:(Timestamp now) on:Transcript
@@ -3287,29 +3292,29 @@
 print:aTimestamp compact:compact asLocal:asLocal asUTC:asUTC withMilliseconds:withMillis timeSeparator:tSep on:aStream
     "Print the given timestamp in general ISO8601 format,
      such as '2014-11-06T11:48:09Z'.
-        compact: if true, the compact format (without separating dashes and colons is generated)
-        asLocal: if true, generates a localtime string (without any timezone info)
-        asUTC: if true, generates a utc string 
-            if both are false:
-                generate a string depending on the type of timestamp:
-                    if local: generate a local timezone string
-                    if utc: generate a utc string
-                    otherwise it is a timestamp from another timezone (TZTimestamp), then print in its timezone
-        withMilliseconds: if false, no milliseconds are generated"
+	compact: if true, the compact format (without separating dashes and colons is generated)
+	asLocal: if true, generates a localtime string (without any timezone info)
+	asUTC: if true, generates a utc string
+	    if both are false:
+		generate a string depending on the type of timestamp:
+		    if local: generate a local timezone string
+		    if utc: generate a utc string
+		    otherwise it is a timestamp from another timezone (TZTimestamp), then print in its timezone
+	withMilliseconds: if false, no milliseconds are generated"
 
     |timeInfo seconds millis |
 
     asLocal ifTrue:[
-        "/ force local
-        timeInfo := aTimestamp asLocalTimestamp timeInfo.
+	"/ force local
+	timeInfo := aTimestamp asLocalTimestamp timeInfo.
     ] ifFalse:[
-        asUTC ifTrue:[
-            "/ force utc
-            timeInfo := aTimestamp asUtcTimestamp timeInfo.
-        ] ifFalse:[
-            "/ in the timestamps own format
-            timeInfo := aTimestamp timeInfo.
-        ]
+	asUTC ifTrue:[
+	    "/ force utc
+	    timeInfo := aTimestamp asUtcTimestamp timeInfo.
+	] ifFalse:[
+	    "/ in the timestamps own format
+	    timeInfo := aTimestamp timeInfo.
+	]
     ].
 
     timeInfo year printOn:aStream leftPaddedTo:4 with:$0.
@@ -3325,20 +3330,20 @@
 
     millis := withMillis ifTrue:[timeInfo milliseconds] ifFalse:[0].
     ((seconds ~= 0) or:[millis ~= 0]) ifTrue:[
-        compact ifFalse:[ aStream nextPut: $:].
-        seconds printOn:aStream leftPaddedTo:2 with:$0.
-        millis ~= 0 ifTrue:[
-            aStream nextPut: $..
-            millis printOn:aStream leftPaddedTo:3 with:$0.
-        ].
+	compact ifFalse:[ aStream nextPut: $:].
+	seconds printOn:aStream leftPaddedTo:2 with:$0.
+	millis ~= 0 ifTrue:[
+	    aStream nextPut: $..
+	    millis printOn:aStream leftPaddedTo:3 with:$0.
+	].
     ].
 
     asUTC ifTrue:[
-        aStream nextPut: $Z
+	aStream nextPut: $Z
     ] ifFalse:[
-        asLocal ifFalse:[
-            self printTimeZone:aTimestamp utcOffset on:aStream.
-        ].
+	asLocal ifFalse:[
+	    self printTimeZone:aTimestamp utcOffset on:aStream.
+	].
     ].
 
     "
@@ -3362,8 +3367,8 @@
     "support for readers which may have already preread the year"
 
     ^ self new
-        yearAlreadyReadAs:yearArg;
-        read:stringOrStream withClass:timestampClass
+	yearAlreadyReadAs:yearArg;
+	read:stringOrStream withClass:timestampClass
 
     "Created: / 15-06-2005 / 17:52:03 / masca"
 ! !
@@ -3377,10 +3382,10 @@
     char isNil ifTrue: [^-1].
 
     ^char isDigit
-        ifTrue: [
-            stream next.
-            char codePoint - $0 codePoint]
-        ifFalse: [-1]
+	ifTrue: [
+	    stream next.
+	    char codePoint - $0 codePoint]
+	ifFalse: [-1]
 
     "Created: / 14-06-2005 / 11:48:52 / masca"
 !
@@ -3390,8 +3395,8 @@
     | digit |
     digit := self nextDigit.
     ^ digit < 0
-        ifTrue: [self malformed: 'No digit found']
-        ifFalse: [digit]
+	ifTrue: [self malformed: 'No digit found']
+	ifFalse: [digit]
 
     "Created: / 15-06-2005 / 10:57:00 / masca"
     "Modified: / 15-06-2005 / 17:22:52 / masca"
@@ -3402,13 +3407,13 @@
     | 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']
+	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
 
@@ -3429,8 +3434,8 @@
     utcOffset := 0.
 
     yearAlreadyRead ~~ true ifTrue:[
-        "Read the year. This will read and swallow up to four year digits."
-        self readYear.
+	"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.
@@ -3438,48 +3443,48 @@
     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].
+	"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].
+	"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.
-            peek == Character space ifTrue:[stream skipSeparators].
-            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]
-        ].
+	ifTrue: [
+	    "Got time signature. Skip the signature, read time and answer the timestamp."
+	    stream next.
+	    peek == Character space ifTrue:[stream skipSeparators].
+	    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].
+	"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.
-            peek == Character space ifTrue:[stream skipSeparators].
-            self readTime.
-            self readTimezone
-        ].
+	ifTrue: [
+	    "Got time signature, expecting time follows. Otherwise only date was in the stream."
+	    stream next.
+	    peek == Character space ifTrue:[stream skipSeparators].
+	    self readTime.
+	    self readTimezone
+	].
 
     ^ self timestampWithClass:timestampClass
 
@@ -3546,29 +3551,29 @@
     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].
+	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].
+	"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]]
+	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"
@@ -3585,87 +3590,87 @@
     peek := stream peekOrNil.
     peek isNil ifTrue: [^self].
     (peek == $:) ifTrue: [
-        "/ read minutes
-        stream next.
-        minute := self nextDigits: 2.
+	"/ read minutes
+	stream next.
+	minute := self nextDigits: 2.
     ] ifFalse: [
-        peek isDigit ifTrue: [
-            "/ read minutes
-            minute := self nextDigits: 2.
-        ] ifFalse:[
-            (peek == $. or:[peek == $,]) ifTrue:[
-                stream next.
-                minute := self readFraction * 60.
-            ] ifFalse:[
-                ^ self.
-            ].
-        ]
+	peek isDigit ifTrue: [
+	    "/ read minutes
+	    minute := self nextDigits: 2.
+	] ifFalse:[
+	    (peek == $. or:[peek == $,]) ifTrue:[
+		stream next.
+		minute := self readFraction * 60.
+	    ] ifFalse:[
+		^ self.
+	    ].
+	]
     ].
 
     minute isInteger ifFalse:[
-        f := minute.
-        minute := f truncated.
-        second := (f - minute) * 60.
-        second isInteger ifFalse:[
-            f := second.
-            second := f truncated.
-            millisecond := (f - second) * 1000.
-            millisecond := millisecond rounded.
-        ].
+	f := minute.
+	minute := f truncated.
+	second := (f - minute) * 60.
+	second isInteger ifFalse:[
+	    f := second.
+	    second := f truncated.
+	    millisecond := (f - second) * 1000.
+	    millisecond := millisecond rounded.
+	].
     ].
     (minute between: 0 and: 59) ifFalse: [self malformed: 'Bad minute: ' , minute printString].
 
     peek := stream peekOrNil.
     peek isNil ifTrue: [^self].
     (peek == $:) ifTrue: [
-        "/ read seconds
-        stream next.
-        second := self nextDigits: 2.
+	"/ read seconds
+	stream next.
+	second := self nextDigits: 2.
     ] ifFalse: [
-        peek isDigit ifTrue: [
-            "/ read seconds
-            second := self nextDigits: 2.
-        ] ifFalse:[
-            (peek == $. or:[peek == $,]) ifTrue:[
-                stream next.
-                second := self readFraction * 60.
-            ] ifFalse:[
-                ^ self.
-            ].
-        ]
+	peek isDigit ifTrue: [
+	    "/ read seconds
+	    second := self nextDigits: 2.
+	] ifFalse:[
+	    (peek == $. or:[peek == $,]) ifTrue:[
+		stream next.
+		second := self readFraction * 60.
+	    ] ifFalse:[
+		^ self.
+	    ].
+	]
     ].
 
     second isInteger ifFalse:[
-        f := second.
-        second := f truncated.
-        millisecond := (f - second) * 1000.
-        millisecond := millisecond rounded.
+	f := second.
+	second := f truncated.
+	millisecond := (f - second) * 1000.
+	millisecond := millisecond rounded.
     ].
     (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]
+	"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."
     ((peek := stream peekOrNil) == $. or:[peek == $,])
-        ifTrue: [
-            "Read dot. Skip it and read milliseconds."
-            stream next.
-            self readMilliseconds].
+	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)']
+	(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"
@@ -3686,27 +3691,27 @@
     "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].
+	ifTrue: [
+	    "Time read, skip Zulu signature and exit."
+	    isUtcTime := true.
+	    stream next.
+	    ^ self].
 
     peek = $+
-        ifTrue: [
-            "Read a plus, expect a negative time zone difference."
-            hasTimezone := true.
-            stream next.
-            self addHoursAndMinutes: (self readTimezoneOffset collect: [:e | e negated]).
-            ^ self].
+	ifTrue: [
+	    "Read a plus, expect a negative time zone difference."
+	    hasTimezone := 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."
-            hasTimezone := true.
-            stream next.
-            self addHoursAndMinutes: self readTimezoneOffset.
-            ^ self].
+	ifTrue: [
+	    "Read a minus, expect positive time zone difference or unknown offset."
+	    hasTimezone := true.
+	    stream next.
+	    self addHoursAndMinutes: self readTimezoneOffset.
+	    ^ self].
 
     "This is local time"
     isUtcTime := false.
@@ -3726,12 +3731,12 @@
     (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].
+	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."
@@ -3754,14 +3759,14 @@
     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'].
-            digit > 7 ifTrue: [self malformed: 'Bad weekday number'].
-            self dateFromWeek: week andWeekday: digit.
-            ^self].
+	ifTrue: [
+	    "Got dash, day number must follow."
+	    stream next.
+	    digit := self nextDigit.
+	    digit < 0 ifTrue: [self malformed: 'Bad weekday number'].
+	    digit > 7 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."
     dayInWeek := self nextDigit.
@@ -3779,11 +3784,11 @@
 
     | read peek |
     stream peekOrNil = $:
-        ifTrue: [
-            "Broken two digit year > 1999 follows."
-            stream next.
-            year := self nextDigitOrError + 2000.
-            ^self].
+	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."
@@ -3794,24 +3799,24 @@
     peek ifNil: [^self].
 
     year := ((peek == $-) or:[peek == $W])
-        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]
-        ]
+	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"
@@ -3820,11 +3825,11 @@
 !Timestamp class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Timestamp.st,v 1.194 2014-11-08 18:22:05 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Timestamp.st,v 1.195 2014-11-10 14:05:01 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Timestamp.st,v 1.194 2014-11-08 18:22:05 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Timestamp.st,v 1.195 2014-11-10 14:05:01 cg Exp $'
 ! !