Timestamp.st
branchjv
changeset 25423 bcfde4da086a
parent 23547 c69c97cec351
child 25431 2ecffe6e5cdf
--- a/Timestamp.st	Mon Oct 26 22:21:00 2020 +0000
+++ b/Timestamp.st	Tue Jun 01 12:09:10 2021 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
@@ -16,7 +14,7 @@
 "{ NameSpace: Smalltalk }"
 
 AbstractTime subclass:#Timestamp
-	instanceVariableNames:'osTime'
+	instanceVariableNames:'osTime additionalPicoseconds'
 	classVariableNames:'Epoch MaxOSTime MinOSTime TimeZoneInfo'
 	poolDictionaries:''
 	category:'Magnitude-Time'
@@ -24,7 +22,7 @@
 
 Object subclass:#TimestampBuilderAbstract
 	instanceVariableNames:'year month day hour minute second millisecond isUtcTime
-		hasTimezone yearAlreadyRead utcOffset'
+		hasTimezone yearAlreadyRead utcOffset picos'
 	classVariableNames:''
 	poolDictionaries:''
 	privateIn:Timestamp
@@ -55,19 +53,21 @@
 
 documentation
 "
-    This class represents time values in milliSeconds starting some time in the past.
+    This class represents time values in milliseconds, starting some time in the past.
+    This base-time is called 'epoch' and always an UTC time.
+
     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 TZTimestamp, which remembers the timezone in which it was created).
 
-    The internal representation, osTime, will typically start with 1970-01-01 0:00,
+    The internal representation, osTime, will typically start with 1970-01-01 00:00 UTC,
     as used in the Unix operating system, but other systems may bias the time differently.
     Actually, the implementation does not depend or even know which time/date
     the OperatingSystem bases its time upon - it is simply keeping the value(s)
     as returned from the OS.
     For conversion, these values are given back to the OS, which will know
-    how to convert these times. This has the advantage, that timestamps on files
+    how to convert them. This has the advantage that timestamps on files
     (such as last-access-time or last-modification-time) can be handled transparently -
     especially when performing comparisons.
 
@@ -77,24 +77,48 @@
     The implementation of this class is not the same as in ST-80
     (which represents the time as seconds from Jan 1., 1901).
 
-    This class should not be confused with Time (which only represents the
-    time within one day). Time instances cannot be used to compare times across midnight;
-    instances of Timestamp can.
-
-    Notice: this class was once called AbsoluteTime. Einstein told us in 1905, that talking
-    about a absolute time is not a good idea (at least in our universe). So the class
-    has been renamed to Timestamp which makes us more compatible to other ST dialects (e.g. VW)
-    AbsoluteTime is still kept as an alias for backward compatibility.
+    This class should not be confused with Time (which only represents the time within one day). 
+    Time instances cannot be used to compare times across midnight, whereas instances of Timestamp can.
+    Also, it should not be confused with TimeDuration, which represents a time-difference.
+
+    Notice: 
+        this class was once called AbsoluteTime. Einstein told us in 1905, that talking
+        about an absolute time is not a good idea (at least in our universe). So in 2004 the class
+        has been renamed to Timestamp which makes us more compatible to other ST dialects (e.g. VW)
+        AbsoluteTime was kept as an alias for backward compatibility and was finally removed in 2017.
 
     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),
+        On UNIX, osTime can only hold dates between 1970-01-01T00:00:00Z and 2038-01-19T03:14:07Z
+        However, timestamp instances can hold negative osTime values (which are timestamps
+        before 1.1.1970 and also osTimes greater than 4294967295 (2^32-1) for timestamps after 2038-01-19.
+        Thus, ST/X will have no problem when dealing with dates before the epoch or after 2038.
+
+        For dates before 1582 (when calendars were changed from Julian to Gregorian),
         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.
 
+    ALso Note:
+        because all timestamps keep the internal time value in UTC, they can be easily compared
+        for being before/same/after another. Only when printing, a difference is made.
+        The timezone is compensated out when a timestamp is created and recalculated in when printed.
+
+    News:
+        The additional instance variable picoSeconds can be used to add more resolution. 
+        If non-nil, it holds additional picoseconds to be added to the millisecond osTime
+        (i.e. the picoSeconds are an integer between 0 and 1000*1000*1000.
+        Although, not all OSs give us that detail when asking for the current time,
+        the picos can still be used in physical computations. 
+        Some OSs will provide microsecond resolution.
+        Notice: 
+            the picos are to be added to the millis, to get picos within the second.
+            this is ugly, but makes all the rest backward compatible.
+            Also, most timestamps only require/have millisecond resolution,
+            so the pico instvar is nil/0 and does not require an aditional largeInteger operation.
+
+        The typical OS-time resolution is in the milli- or microsecond range.
+        External logging hardware may generate timestamps in the micro- or nanosecond range.
+        Picosecond resolution should be good enough for almost any application (at least for the near future).
+
     [author:]
         Claus Gittinger
 
@@ -139,6 +163,29 @@
     "Modified: / 13.7.1999 / 12:42:30 / stefan"
 !
 
+UTCYear:y month:m day:d hour:h minute:min second:s millisecond:millis additionalPicoseconds:picos
+    "return an instance of the receiver, given individual components,
+     interpreted in the UTC timezone."
+
+    ^ self basicNew
+        UTCyear:y month:m day:d hour:h minute:min second:s millisecond:millis
+        additionalPicoseconds:picos
+
+    "
+     Timestamp UTCYear:1970 month:1 day:1 hour:0 minute:0 second:0 millisecond:0
+     Timestamp UTCYear:1991 month:1 day:2 hour:12 minute:30 second:0 millisecond:0
+     Timestamp UTCYear:1991 month:1 day:2 hour:12 minute:30 second:0 millisecond:100
+     Timestamp UTCYear:1999 month:7 day:1 hour:1 minute:0 second:0 millisecond:0
+     Timestamp UTCYear:2000 month:1 day:1 hour:1 minute:0 second:0 millisecond:0
+
+     UtcTimestamp UTCYear:2000 month:1 day:1 hour:1 minute:0 second:0 millisecond:0
+    "
+
+    "Modified: / 1.7.1996 / 15:22:07 / cg"
+    "Created: / 13.7.1999 / 12:34:37 / stefan"
+    "Modified: / 13.7.1999 / 12:42:30 / stefan"
+!
+
 decodeFromLiteralArray:anArray
     "decode a Timestamp literalArray.
 
@@ -231,6 +278,78 @@
     "Modified: / 13.7.1999 / 12:30:47 / stefan"
 !
 
+fromDate:aDate hour:hour minute:minute second:second
+    "return an instance of the receiver, initialized from a time and a date object.
+     See also `Timestamp now' and other protocol inherited from my superclass."
+
+    ^ self fromDate:aDate hour:hour minute:minute second:second millisecond:0
+
+    "
+     Timestamp fromDate:(Date today) andTime:(Time now)
+     Timestamp fromDate:(Date today) hour:10 minute:5 second:30
+    "
+!
+
+fromDate:aDate hour:hour minute:minute second:second microsecond:micros
+    "return an instance of the receiver, initialized from a time and a date object.
+     See also `Timestamp now' and other protocol inherited from my superclass."
+
+    ^ (self
+        year:aDate year
+        month:aDate month
+        day:aDate day
+        hour:hour
+        minute:minute
+        second:second
+        millisecond:0
+      ) setMicrosecond:micros
+
+    "
+     Timestamp fromDate:(Date today) hour:10 minute:5 second:30 microsecond:123456
+     Timestamp fromDate:(Date today) hour:10 minute:5 second:30 microsecond:140
+    "
+!
+
+fromDate:aDate hour:hour minute:minute second:second millisecond:millis
+    "return an instance of the receiver, initialized from a time and a date object.
+     See also `Timestamp now' and other protocol inherited from my superclass."
+
+    ^ self
+        year:aDate year
+        month:aDate month
+        day:aDate day
+        hour:hour
+        minute:minute
+        second:second
+        millisecond:millis
+
+    "
+     Timestamp fromDate:(Date today) andTime:(Time now)
+     Timestamp fromDate:(Date today) andTime:(Time nowWithMilliseconds)
+     Timestamp fromDate:(Date today) hour:10 minute:5 second:30 millisecond:140
+    "
+!
+
+fromDate:aDate hour:hour minute:minute second:second nanosecond:nanos
+    "return an instance of the receiver, initialized from a time and a date object.
+     See also `Timestamp now' and other protocol inherited from my superclass."
+
+    ^ (self
+        year:aDate year
+        month:aDate month
+        day:aDate day
+        hour:hour
+        minute:minute
+        second:second
+        millisecond:0
+      ) setNanosecond:nanos
+
+    "
+     Timestamp fromDate:(Date today) hour:10 minute:5 second:30 microsecond:123456
+     Timestamp fromDate:(Date today) hour:10 minute:5 second:30 microsecond:140
+    "
+!
+
 newDay:dayInYear year:year
     "return a new Timestamp, given the year and the day-in-year (starting at 1).
      Date protocol compatibility"
@@ -246,15 +365,19 @@
 !
 
 secondsSince1970:secs
-    "set time from elapsed seconds since 1-1-1970, 00:00:00.
-     This is the format used in the UNIX world"
+    "set time from elapsed seconds since 1-1-1970, 00:00:00 (UTC).
+     This is the format used in the UNIX world.
+     Notice that the internal storage is always UTC based."
 
     ^ self basicNew setSeconds:secs.
 
     "
-     Timestamp secondsSince1970:0
+     UtcTimestamp secondsSince1970:0        -> 1970-01-01 00:00:00Z       
+     Timestamp secondsSince1970:0           -> 1970-01-01 01:00:00 (local germany, ST)
+
      Timestamp secondsSince1970:3600
      Timestamp secondsSince1970:3600*24
+
      (Timestamp year:2010 month:7 day:1 hour:0 minute:0 second:0)
        =
      (Timestamp secondsSince1970:1277935200)
@@ -265,12 +388,13 @@
     "Modified: / 08-01-2011 / 16:06:28 / cg"
 !
 
-utcMillisecondsSince1970:secs
+utcMillisecondsSince1970:millis
     "set time from elapsed milliseconds since the epoch 1-1-1970, 00:00:00."
 
-    ^ self basicNew setMilliseconds:secs
+    ^ self basicNew setMilliseconds:millis
 
     "Created: / 08-01-2011 / 16:09:32 / cg"
+    "Modified (format): / 14-12-2018 / 19:45:12 / Claus Gittinger"
 !
 
 utcNow
@@ -285,19 +409,19 @@
 !
 
 utcSecondsSince1970:secs
-    "set time from elapsed seconds since 1-1-1970, 00:00:00.
-     This is the format used in the UNIX world"
-
-    ^ self secondsSince1970:secs
-
-"/    |divMod|
-"/
-"/    divMod := secs divMod:3600.
-"/    ^ self year:1970 month:1 day:1 hour:(divMod at:1) minute:0 second:(divMod at:2) millisecond:0.
-
-    "
-     Timestamp secondsSince1970:0
-     Timestamp secondsSince1970:3600
+    "set time from the elapsed seconds since 1-1-1970, 00:00:00 UTC.
+     This is the format used in the UNIX world.
+     Notice that the internal storage is always UTC based."
+
+    ^ UtcTimestamp secondsSince1970:secs
+
+    "
+     UtcTimestamp secondsSince1970:0        -> 1970-01-01 00:00:00Z       
+     Timestamp secondsSince1970:0           -> 1970-01-01 01:00:00 (local germany, ST)
+
+     UtcTimestamp secondsSince1970:3600     -> 1970-01-01 01:00:00Z
+     Timestamp secondsSince1970:3600        -> 1970-01-01 02:00:00 (local)
+
      Timestamp secondsSince1970:3600*24
     "
 
@@ -343,6 +467,18 @@
     "Modified: / 13.7.1999 / 12:27:47 / stefan"
 !
 
+year:y month:m day:d hour:h minute:min second:s microsecond:micros
+    "return an instance of the receiver, given individual components.
+     See also `Timestamp now' and other protocol inherited
+     from my superclass."
+
+    ^ (self year:y month:m day:d hour:h minute:min second:s) setMicrosecond:micros
+
+    "
+     Timestamp year:1991 month:1 day:2 hour:12 minute:30 second:0 microsecond:100
+    "
+!
+
 year:y month:m day:d hour:h minute:min second:s millisecond:millis
     "return an instance of the receiver, given individual components.
      See also `Timestamp now' and other protocol inherited
@@ -361,6 +497,28 @@
     "Modified: / 1.7.1996 / 15:22:07 / cg"
     "Created: / 13.7.1999 / 12:28:44 / stefan"
     "Modified: / 13.7.1999 / 12:37:57 / stefan"
+!
+
+year:y month:m day:d hour:h minute:min second:s millisecond:millis additionalPicoseconds:picos
+    "return an instance of the receiver, given individual components.
+     See also `Timestamp now' and other protocol inherited
+     from my superclass."
+
+    ^ self basicNew
+            year:y month:m day:d hour:h minute:min second:s 
+            millisecond:millis additionalPicoseconds:picos 
+
+    "
+     Timestamp year:1970 month:1 day:1 hour:0 minute:0 second:0
+     Timestamp year:1991 month:1 day:2 hour:12 minute:30 second:0
+     Timestamp year:1991 month:1 day:2 hour:12 minute:30 second:0 millisecond:100
+     Timestamp year:2000 month:7 day:1 hour:1 minute:0 second:0
+     UtcTimestamp year:2000 month:7 day:1 hour:1 minute:0 second:0
+    "
+
+    "Modified: / 1.7.1996 / 15:22:07 / cg"
+    "Created: / 13.7.1999 / 12:28:44 / stefan"
+    "Modified: / 13.7.1999 / 12:37:57 / stefan"
 ! !
 
 !Timestamp class methodsFor:'Compatibility-Squeak'!
@@ -374,7 +532,9 @@
 
     ^ self
         readFrom:aStringOrStream
-        onError:[ TimeConversionError raiseRequestWith:aStringOrStream errorString:' - timestamp']
+        onError:[ 
+            TimeConversionError raiseRequestWith:aStringOrStream errorString:' - timestamp'
+        ]
 
     "
      self readFrom:'23-jun-2000 15:00'
@@ -383,6 +543,22 @@
     "
 
     "Modified (comment): / 20-08-2011 / 16:52:10 / cg"
+    "Modified (format): / 14-12-2018 / 19:14:16 / Claus Gittinger"
+!
+
+year:year day:dayInYear
+    "return a new Timestamp, given the year and the day-in-year (starting at 1).
+     See also: Date today / Time now / Timestamp now.
+     Squeak compatibility"
+
+    ^ self newDay:dayInYear year:year
+
+    "
+     self year:1970 day:1
+     self year:2000 day:1
+    "
+
+    "Created: / 26-05-2019 / 11:59:20 / Claus Gittinger"
 !
 
 year: year month: month day: day hour: hour minute: minute second: second millisecond: millisecond offset:timeDuration
@@ -400,7 +576,20 @@
 
     "
      Timestamp year:2015 month:11 day:9 hour:12 minute:0 second:0 offset:(2 hours)
-    "
+     Timestamp year:2015 month:11 day:9 hour:12 minute:0 second:0 offset:0
+    "
+
+    "Modified (comment): / 26-05-2019 / 12:10:28 / Claus Gittinger"
+! !
+
+!Timestamp class methodsFor:'class access'!
+
+timestampISO8601Builder
+    "I hate private class overuse...
+     ... I need such ugly hacks whenever someone thinks that he/she must keep a secret...
+     See Time for such its use"
+
+    ^ TimestampISO8601Builder
 ! !
 
 !Timestamp class methodsFor:'format strings'!
@@ -450,24 +639,25 @@
 
 newDay:day month:month year:year
     <resource: #obsolete>
+
     "return a new Timestamp, given the year, month and day (starting at 1).
-     Date protocol compatibility"
+     Date protocol compatibility.
+     Obsolete: use year:month:day:."
 
     ^ 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
     "
 ! !
 
-
 !Timestamp class methodsFor:'private'!
 
 basicReadFrom:aStream
@@ -482,46 +672,61 @@
      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.
+        or (us-format, for Travis) mm/dd/yyyy hh:mm:ss.iii
+        or (us-format with year first) yyyy-mm-ddThh:mm:ss.iii
      On error, raise an exception"
 
-    |monthOrYear firstNumber secondNumber day month year hour min sec millis usFormat possibeMonthName ch utcOffsetOrNil count|
-
-    count := 0.
-    monthOrYear := aStream throughAnyForWhich:[:ch | count := count+1. ch isDigit and:[count <= 4]].
-    firstNumber := Integer readFrom:monthOrYear onError:[TimeConversionError raiseErrorString:' - integer expected'].
-    firstNumber > 31 ifTrue:[
-        "/ assume iso8601 format;
-        ^ self readIso8601FormatFrom:aStream yearAlreadyRead:firstNumber.
-    ].
-    aStream skipSeparators.
-
-    "/ consider this a kludge
-    usFormat := (aStream peek == $/ ).
-
-    [(ch := aStream peekOrNil) notNil and:[ch isLetterOrDigit]] whileFalse:[aStream next].
-    (ch notNil and:[ch isDigit]) ifTrue:[
-        secondNumber := Integer readFrom:aStream onError:-1.
-
-        usFormat ifTrue:[
-            month := firstNumber.
-            day := secondNumber.
+    |monthOrYear firstNumber secondNumber day month year hour min sec 
+     millis usFormat possibeMonthName ch utcOffsetOrNil 
+     mantissa fraction picos ts
+     monthName|
+
+    aStream skipSeparators isLetter ifTrue:[
+        "/ US format, like 'July 21, 1983 01:15:00' ?
+        monthName := aStream throughAnyForWhich:[:ch | ch isLetter].
+        month := Date indexOfMonth:monthName asLowercase.
+        aStream skipSeparators.
+        day := Integer readFrom:aStream onError:-1.
+        aStream skipSeparators == $, ifTrue:[
+            aStream next
+        ].
+    ] ifFalse:[
+        monthOrYear := aStream throughAnyAtMost:4 forWhich:[:ch | ch isDigit].
+        firstNumber := Integer readFrom:monthOrYear onError:[TimeConversionError raiseErrorString:' - integer expected'].
+        firstNumber > 31 ifTrue:[
+            "/ assume iso8601 format;
+            ^ self readIso8601FormatFrom:aStream yearAlreadyRead:firstNumber.
+        ].
+
+        "/ consider this a kludge
+        usFormat := aStream skipSeparators == $/.
+
+        [(ch := aStream peekOrNil) notNil and:[ch isLetterOrDigit not]] whileTrue:[aStream next].
+        (ch notNil and:[ch isDigit]) ifTrue:[
+            secondNumber := Integer readFrom:aStream onError:-1.
+
+            usFormat ifTrue:[
+                month := firstNumber.
+                day := secondNumber.
+            ] ifFalse:[
+                month := secondNumber.
+                day := firstNumber.
+            ].
         ] ifFalse:[
-            month := secondNumber.
+            possibeMonthName := aStream throughAnyForWhich:[:ch | ch isLetter].
+            month := Date indexOfMonth:possibeMonthName asLowercase.
             day := firstNumber.
         ].
-    ] ifFalse:[
-        possibeMonthName := aStream throughAnyForWhich:[:ch | ch isLetter].
-        month := Date indexOfMonth:possibeMonthName asLowercase.
-        day := firstNumber.
     ].
-
+    
     (day between:1 and:31) ifFalse:[ TimeConversionError raiseErrorString:' - bad day' ].
     (month between:1 and:12) ifFalse:[ TimeConversionError raiseErrorString:' - bad month' ].
 
     [(ch := aStream peekOrNil) notNil and:[ch isDigit not]] whileTrue:[aStream next].
     year := Integer readFrom:aStream onError:[ TimeConversionError raiseErrorString:' - bad year' ].
 
+    picos := 0.
+
     aStream atEnd ifTrue:[
         hour := min := sec := millis := 0.
     ] ifFalse:[
@@ -540,10 +745,19 @@
             sec := Integer readFrom:aStream onError:-1.
             (sec between:0 and:59) ifFalse:[ TimeConversionError raiseErrorString:' - bad second' ].
 
-            aStream peek == $. ifTrue:[
+            ((ch := aStream peek) == $. or:[ch == $,]) ifTrue:[
                 aStream next.
-                millis := Integer readFrom:aStream onError:0.
-                millis >= 1000 ifTrue:[ TimeConversionError raiseErrorString:' - bad millisecond' ].
+                mantissa := Number readMantissaAndScaleFrom:aStream radix:10.
+                fraction := (mantissa at:2) / (10 raisedTo:(mantissa at:3)).
+                (mantissa at:3) > 3 ifTrue:[
+                    picos := fraction * (1000 * 1000 * 1000 * 1000).
+                    millis := picos // (1000 * 1000 * 1000).
+                    picos := picos \\ (1000 * 1000 * 1000).
+                ] ifFalse:[
+                    millis := fraction * 1000.
+                ].
+                "/ millis := Integer readFrom:aStream onError:0.
+                "/ millis >= 1000 ifTrue:[ TimeConversionError raiseErrorString:' - bad millisecond' ].
             ] ifFalse:[
                 millis := 0.
             ].
@@ -558,18 +772,25 @@
     hour == 24 ifTrue:[
         (min ~~ 0 or:[sec ~~ 0 or:[millis ~~ 0]]) ifTrue:[ TimeConversionError raiseErrorString:' - bad hour' ].
     ].
+
     utcOffsetOrNil notNil ifTrue:[
         utcOffsetOrNil = 0 ifTrue:[
             "/ utc timestamp
-            ^ UtcTimestamp year:year month:month day:day hour:hour minute:min second:sec millisecond:millis
+            ts := UtcTimestamp year:year month:month day:day hour:hour minute:min second:sec millisecond:millis
+        ] ifFalse:[
+            "/ tz timestamp
+            ts := ((TZTimestamp basicNew 
+                    setOSTimeFromUTCYear:year month:month day:day 
+                    hour:hour minute:min second:sec millisecond:millis
+                    ) utcOffset:utcOffsetOrNil
+                  ) addSeconds:utcOffsetOrNil.
         ].
-        ^ TZTimestamp new 
-                UTCyear:year month:month day:day hour:hour minute:min second:sec millisecond:millis;
-                utcOffset:utcOffsetOrNil;
-                addSeconds:utcOffsetOrNil.
+    ] ifFalse:[
+        "/ a local timestamp
+        ts := self year:year month:month day:day hour:hour minute:min second:sec millisecond:millis.
     ].
-    "/ a local timestamp
-    ^ self year:year month:month day:day hour:hour minute:min second:sec millisecond:millis.
+    picos ~~ 0 ifTrue:[ ts additionalPicoseconds:picos ].
+    ^ ts
 
     "some ad hoc formats:
 
@@ -595,13 +816,21 @@
      Timestamp basicReadFrom:'foo' readStream
 
      any iso8601 format:.
-     Timestamp basicReadFrom:(Timestamp now printString readStream)
-     Timestamp basicReadFrom:'1995-10-20 24:00:00.000' readStream
-     Timestamp basicReadFrom:'1995-10-20 12:10:00.000' readStream
-     Timestamp basicReadFrom:'1995-10-20 12:10:00.000-0200' readStream
+     Timestamp basicReadFrom:(Timestamp now printString readStream)    
+     Timestamp basicReadFrom:'1995-10-20 24:00:00.000' readStream      
+     Timestamp basicReadFrom:'1995-10-20 12:10:00.000' readStream      
+     Timestamp basicReadFrom:'1995-10-20 12:10:00.000-0200' readStream 
+
+     Timestamp basicReadFrom:'1995-10-20T12:10:00.000' readStream
+     Timestamp basicReadFrom:'2018-03-30T03:24:00'readStream  
+     Timestamp basicReadFrom:'2018-3-30T03:24:00'readStream   
 
      UtcTimestamp basicReadFrom:'1995-10-20 12:10:00.000' readStream
     "
+
+    "Modified: / 09-11-2017 / 10:10:07 / cg"
+    "Modified: / 14-12-2018 / 19:22:17 / Claus Gittinger"
+    "Modified: / 28-09-2019 / 15:24:25 / Stefan Vogel"
 !
 
 readIso8601FormatFrom:aStringOrStream yearAlreadyRead:yearOrNil
@@ -794,14 +1023,11 @@
 readIso8601FormatFrom:aStringOrStream yearAlreadyRead:yearOrNil onError:exceptionValue
     "common helper for read methods."
 
-    |retVal|
-
-    ConversionError handle:[:ex |
-	retVal := exceptionValue value
-    ] do:[
-	retVal := self readIso8601FormatFrom:aStringOrStream yearAlreadyRead:yearOrNil
-    ].
-    ^ retVal
+    ^ [
+        self readIso8601FormatFrom:aStringOrStream yearAlreadyRead:yearOrNil
+    ] on:ConversionError do:exceptionValue.
+
+    "Modified: / 09-02-2017 / 10:01:27 / stefan"
 ! !
 
 !Timestamp class methodsFor:'reading'!
@@ -818,7 +1044,9 @@
         %s      seconds, 00..59                0-padded to length 2
         %i      milliseconds, 000..999         0-padded to length 3
         %f      fractional seconds             any length, but only milliseconds kept
+        %F      fractional seconds             any length, up to picoseconds kept
         %a      am/pm
+        %tz     timezone
 
         %d             - day
         %D             - day
@@ -837,6 +1065,7 @@
         %Y2000          - year, last 2 digits only, map to 2000..2099
         %Y1950          - year, last 2 digits only, map to 1950..2049
         %Y1980          - year, last 2 digits only, map to 1980..2079
+        %Y1970          - year, last 2 digits only, map to 1970..2069
 
      an optional length after the % gives a field length;
         i.e. %2h%2m%2s parses '123557' as 12:35:37
@@ -848,7 +1077,7 @@
     |day month year dayOfYear monthAndDay
      hour minute second millisecond
      utcOffset inStream formatStream error fChar format itemHandler
-     len now s fractionString fraction|
+     len s fractionString fraction picos ts|
 
     error := [:msg |
                 exceptionalValue isBlock ifTrue:[
@@ -911,6 +1140,15 @@
                 year := year + 1900
             ]  
 
+        ] ifFalse:[ ( format sameAs:  'Y1970' ) ifTrue:[
+            year := Integer readFrom:input onError:[ error value:'invalid year' ].
+            (year between:0 and: 99) ifFalse:[ error value:'invalid year' ].
+            (year between:0 and: 69) ifTrue:[ 
+                year := year + 2000
+            ] ifFalse:[    
+                year := year + 1900
+            ]  
+
         ] ifFalse:[ ( format sameAs:  'Y2000' ) ifTrue:[
             year := Integer readFrom:input onError:[ error value:'invalid year' ].
             (year between:0 and: 99) ifFalse:[ error value:'invalid year' ].
@@ -934,8 +1172,13 @@
         ] ifFalse:[ ( format = 'f'  or:[ format = 'F' ]) ifTrue:[
             fractionString := input upToMatching:[:ch | ch isDigit not].
             fraction := FixedPoint readFrom:'0.',fractionString.
-            millisecond := (fraction * 1000) truncated.
-
+            format = 'f' ifTrue:[
+                millisecond := (fraction * 1000) truncated.
+            ] ifFalse:[
+                picos := (fraction * 1000*1000*1000*1000) truncated.
+                millisecond := picos // (1000*1000*1000).
+                picos := picos \\ (1000*1000*1000).
+            ].
         ] ifFalse:[ ( format = 'tz' ) ifTrue:[
             utcOffset := self utcOffsetFrom:input.
             utcOffset isNil ifTrue:[ error value:'invalid timezone' ]
@@ -954,14 +1197,13 @@
 
         ] ifFalse:[
             error value:'unhandled format:',format
-        ]]]]]]]]]]]]]]]]]]
+        ]]]]]]]]]]]]]]]]]]]
     ].
 
     hour := 0.
     minute := 0.
     second := 0.
     millisecond := 0.
-    utcOffset := 0.
 
     inStream := aStringOrStream readStream.
     formatStream := formatString readStream.
@@ -969,7 +1211,7 @@
     [formatStream atEnd] whileFalse:[
         fChar := formatStream next.
         fChar = Character space ifTrue:[
-            inStream peek isSeparator ifFalse:[ error value: 'format error; space expcected' ].
+            inStream peek isSeparator ifFalse:[ error value: 'format error; space expeccted' ].
             inStream skipSeparators.
         ] ifFalse:[
             fChar == $% ifTrue:[
@@ -1001,7 +1243,7 @@
     ].
 
     year isNil ifTrue:[
-        year := (now := Timestamp now) year
+        year := Timestamp now year
     ].
     
     dayOfYear notNil ifTrue:[
@@ -1009,11 +1251,28 @@
         month := (monthAndDay at:1).
         day := (monthAndDay at:2).  
     ].
-    
-    ^ (self 
-        year:year month:month day:day 
-        hour:(hour ? 0) minute:(minute ? 0) second:(second ? 0) millisecond:millisecond) 
-            + utcOffset
+
+    utcOffset notNil ifTrue:[
+        utcOffset == 0 ifTrue:[
+            ts := (UtcTimestamp 
+                year:year month:month day:day 
+                hour:(hour ? 0) minute:(minute ? 0) second:(second ? 0) millisecond:millisecond)
+        ] ifFalse:[
+            ts := ((TZTimestamp basicNew
+                    setOSTimeFromUTCYear:year month:month day:day 
+                    hour:(hour ? 0) minute:(minute ? 0) second:(second ? 0) millisecond:millisecond
+               ) utcOffset:utcOffset
+              ) addSeconds:utcOffset.
+        ]              
+    ] ifFalse:[
+        ts := (self 
+            year:year month:month day:day 
+            hour:(hour ? 0) minute:(minute ? 0) second:(second ? 0) millisecond:millisecond) 
+    ].
+    picos notNil ifTrue:[
+        ts additionalPicoseconds:picos
+    ].
+    ^ ts.
 
     "
      Timestamp readFrom:'20-2-1995 13:11:06' format:'%day-%month-%year %h:%m:%s' language:nil onError:[self halt]
@@ -1036,6 +1295,8 @@
      Timestamp readFrom:'20-2-1995 13:11:06.001' format:'%day-%month-%year %h:%m:%s.%f' language:nil onError:[self halt]
      Timestamp readFrom:'20-2-1995 13:11:06.12345' format:'%day-%month-%year %h:%m:%s.%f' language:nil onError:[self halt]
     "
+
+    "Modified: / 28-09-2019 / 15:25:17 / Stefan Vogel"
 !
 
 readFrom:aStringOrStream onError:exceptionBlock
@@ -1183,7 +1444,7 @@
 
 
     ^ [
-        |newTime str day month year hour min sec millis c|
+        |newTime str day month year hour min sec millis c fraction|
 
         sec := millis := 0.
         str := aStringOrStream readStream.
@@ -1211,20 +1472,24 @@
         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 peekOrNil == $: ifTrue:[ str next].
+        sec := Integer readFrom:(str next:2).
+        (sec between:0 and:59) ifFalse:[^ exceptionBlock value].
+        str peekOrNil == $. ifTrue:[
+            str next.
+            "/ the old code here was wrong in assuming that exactly 3 digits
+            "/ are coming; thus hh:mm:ss.1 was interpreted as 1ms (instead of 100)
+            "/ thus: count the zeros...
+            str peek isDigit ifTrue:[
+                fraction := Number readMantissaFrom:str radix:10.
+                fraction isNil ifTrue:[^ exceptionBlock value].
+                millis := (fraction * 1000) rounded.
+            ] ifFalse:[
+                millis := 0
             ].
         ].
 
-        str atEnd ifTrue:[
+        str skipSeparators isNil ifTrue:[
             "/ this is local time
             newTime := self year:year month:month day:day
                             hour:hour minute:min second:sec millisecond:millis.
@@ -1291,31 +1556,28 @@
 
     "Modified: / 13-07-1999 / 12:31:14 / stefan"
     "Modified: / 22-08-2006 / 12:30:11 / cg"
+    "Modified: / 22-10-2019 / 16:09:25 / Stefan Vogel"
 !
 
 readISO8601From:aStringOrStream
-    "Please use this format for all external representations - it's the standard."
-
-    "using the new reader"
-
-    ^ TimestampISO8601Builder read:aStringOrStream withClass:self
+    "obsoleted due to uc/lc confusion"
+
+    <resource: #obsolete>
+
+    ^ self readIso8601FormatFrom:aStringOrStream
 
     "Created: / 16-06-2005 / 16:13:36 / masca"
+    "Modified: / 09-02-2017 / 10:04:53 / stefan"
 !
 
 readISO8601From:aStringOrStream onError:exceptionValue
-    "Please use this format for all external representations - it's the standard."
-
-    "using the new reader"
-
-    |retVal|
-
-    ConversionError handle:[:ex |
-	retVal := exceptionValue value
-    ] do:[
-	retVal := TimestampISO8601Builder read:aStringOrStream withClass:self
-    ].
-    ^ retVal
+    "obsoleted due to uc/lc confusion"
+
+    <resource: #obsolete>
+
+    ^ self readIso8601FormatFrom:aStringOrStream onError:exceptionValue
+
+    "Modified: / 09-02-2017 / 10:05:56 / stefan"
 !
 
 readIso8601FormatFrom:aStringOrStream
@@ -1370,19 +1632,16 @@
      Please use this format for all external representations - it's the standard."
 
     "/ changed to use the new reader
-    |retVal|
-
-    ConversionError handle:[:ex |
-	retVal := exceptionValue value
-    ] do:[
-	retVal := TimestampISO8601Builder read:aStringOrStream withClass:self
-    ].
-    ^ retVal
+    ^ [
+        TimestampISO8601Builder read:aStringOrStream withClass:self
+    ] on:ConversionError do:exceptionValue.
 
 "/    ^ self
 "/        readIso8601FormatFrom:aStringOrStream
 "/        yearAlreadyRead:nil
 "/        onError:exceptionValue
+
+    "Modified: / 09-02-2017 / 10:02:03 / stefan"
 !
 
 readRFC1123FormatFrom:rfc1123String onError:exceptionBlock
@@ -1446,10 +1705,17 @@
         ].
     ].
 
-    day := Integer readFrom:(parts at:2 + indexModifier) onError:[^ exceptionBlock].
-    year := Integer readFrom:(parts at:4 + indexModifier) onError:[^ exceptionBlock].
-    time := Time readFrom:(parts at:5 + indexModifier) onError:[^ exceptionBlock].
-    monthName := parts at:3 + indexModifier.
+    (parts at:2 + indexModifier) first isDigit ifTrue:[
+        day := Integer readFrom:(parts at:2 + indexModifier) onError:[^ exceptionBlock].
+        year := Integer readFrom:(parts at:4 + indexModifier) onError:[^ exceptionBlock].
+        monthName := parts at:3 + indexModifier.
+        time := Time readFrom:(parts at:5 + indexModifier) onError:[^ exceptionBlock].
+    ] ifFalse:[
+        monthName := (parts at:2 + indexModifier).
+        day := Integer readFrom:(parts at:3 + indexModifier) onError:[^ exceptionBlock].  
+        year := Integer readFrom:(parts at:5 + indexModifier) onError:[^ exceptionBlock].  
+        time := Time readFrom:(parts at:4 + indexModifier) onError:[^ exceptionBlock].
+    ].
 
     month := Date indexOfMonth:monthName language:#en.
     month = 0 ifTrue:[^ exceptionBlock value].
@@ -1460,10 +1726,11 @@
     (utcOffset isNil or:[utcOffset = 0]) ifTrue:[
         ^ UtcTimestamp year:year month:month day:day hour:time hour minute:time minute second:time second millisecond:0.
     ].
-    ^ TZTimestamp new 
-            setOSTimeFromUTCYear:year month:month day:day hour:time hour minute:time minute second:time second millisecond:0;
-            utcOffset:utcOffset;
-            addSeconds:utcOffset.
+    ^ ((TZTimestamp new 
+            setOSTimeFromUTCYear:year month:month day:day 
+            hour:time hour minute:time minute second:time second millisecond:0
+       ) utcOffset:utcOffset
+      ) addSeconds:utcOffset.
 
     "
      self readRFC1123FormatFrom:'Mon, 17 Aug 2009 11:11:15 GMT' onError:nil
@@ -1472,6 +1739,7 @@
      self readRFC1123FormatFrom:'Mon, 17 Aug 2009 11:11:15 PDT' onError:nil
      self readRFC1123FormatFrom:'Mon, 17 Aug 2009 11:11:15 +0100' onError:nil
      self readRFC1123FormatFrom:'17 Aug 2009 11:11:15 +0100' onError:nil
+     self readRFC1123FormatFrom:'Thu Jul 4 15:04:40 2019 +0200' onError:nil
     "
 
     "Modified: / 05-10-2010 / 16:05:32 / cg"
@@ -1577,7 +1845,7 @@
             'IDLW' -720 false          "/ international date line west
             'IDLE'  720 false          "/ international date line east
 
-            'MEZ'   60  false           "/ mittel europäische Zeit /  central european (german)
+            'MEZ'   60  false           "/ mittel europäische Zeit /  central european (german)
             'MESZ'  120 true            "/ central european summer (german)
             'WESZ'  60  true            "/ west european summer (german)
 
@@ -1658,9 +1926,8 @@
     |ch offset stream|
 
     stream := aStringOrStream readStream.
-    stream skipSeparators.
-
-    ch := stream peekOrNil.
+
+    ch := stream skipSeparators.
     ch isNil ifTrue:[^ 0].
 
     ch isLetter ifTrue:[
@@ -1711,6 +1978,8 @@
      self utcOffsetFrom:'+1:30'
      self utcOffsetFrom:'+01'
     "
+
+    "Modified: / 28-09-2019 / 15:25:45 / Stefan Vogel"
 !
 
 utcOffsetFromString:aString
@@ -1726,7 +1995,6 @@
     "
 ! !
 
-
 !Timestamp methodsFor:'accessing'!
 
 day
@@ -1811,14 +2079,143 @@
     "Created: / 20-01-2011 / 12:28:46 / cg"
 !
 
-hour
-    "return the hour (0..23).
-     ST-80 Timestamp compatibility (I'd prefer the name #hours, for Time compatibility)."
-
-    ^ self hours
-
-    "Created: 1.7.1996 / 15:14:50 / cg"
-    "Modified: 1.7.1996 / 15:15:32 / cg"
+exactMicroseconds
+    "return the exact microseconds within the stamp's second (0 .. 999.999...) as a fixedPoint number.
+     notice: 
+        that is NOT the total number of microseconds,
+        but the fractional part (within the second) only.
+     A fixedPoint number holds the exact value, but prints itself rounded!!"
+
+    |millis microsFromMillis|
+
+    millis := (osTime \\ 1000).
+    microsFromMillis := millis * 1000.
+    additionalPicoseconds notNil ifTrue:[
+        ^ microsFromMillis + (FixedPoint numerator:additionalPicoseconds denominator:(1000*1000) scale:3)
+    ].
+    ^ microsFromMillis.
+
+    "
+     |ts|
+
+     ts := Timestamp nowWithMicroseconds.
+     Transcript showCR:ts.
+     Transcript showCR:ts microseconds.
+     Transcript showCR:ts exactMicroseconds.
+     Transcript showCR:ts nanoseconds.
+     Transcript showCR:ts picoseconds.
+    "
+!
+
+exactMilliseconds
+    "return the exact milliseconds within the stamp's second (0 .. 999.999...) as a fixedPoint number.
+     notice: 
+        that is NOT the total number of microseconds,
+        but the fractional part (within the second) only.
+     A fixedPoint number holds the exact value, but prints itself rounded!!"
+
+    |millis|
+
+    millis := (osTime \\ 1000).
+    additionalPicoseconds notNil ifTrue:[
+        ^ millis + (FixedPoint numerator:additionalPicoseconds denominator:(1000*1000*1000) scale:3)
+    ].
+    ^ millis.
+
+    "
+     |ts|
+
+     ts := Timestamp nowWithMicroseconds.
+     Transcript showCR:ts.
+     Transcript showCR:ts milliseconds.
+     Transcript showCR:ts exactMilliseconds.
+     Transcript showCR:ts microseconds.
+     Transcript showCR:ts nanoseconds.
+     Transcript showCR:ts picoseconds.
+    "
+!
+
+exactMinutes
+    "return the exact minutes within the stamp's hour (00 .. 59.999...) as a fixedPoint number.
+     Notice: 
+        that is NOT the total number of minutes,
+        but the fractional part (within the hour) only.
+     A fixedPoint number holds the exact value, but prints itself rounded!!"
+
+    |minutes additionalSeconds|
+
+    minutes := FixedPoint numerator:(osTime \\ (60*60*1000)) / 60 denominator:1000 scale:3.
+    additionalPicoseconds notNil ifTrue:[
+        additionalSeconds := (FixedPoint numerator:additionalPicoseconds denominator:(1000*1000*1000*1000) scale:3).
+        minutes := minutes + (additionalSeconds / 60).
+    ].
+    ^ minutes.
+
+    "
+     |ts|
+
+     ts := Timestamp nowWithMicroseconds.
+     Transcript showCR:ts.
+     Transcript showCR:ts minutes.
+     Transcript showCR:ts exactMinutes.
+    "
+!
+
+exactNanoseconds
+    "return the exact nanoseconds within the stamp's second (0 .. 999.999...).
+     notice: 
+        that is NOT the total number of nanoseconds,
+        but the fractional part (within the second) only.
+     A fixedPoint number holds the exact value, but prints itself rounded!!"
+
+    |millis nanosFromMillis|
+
+    millis := (osTime \\ 1000).
+    nanosFromMillis := millis * 1000 * 1000.
+    additionalPicoseconds notNil ifTrue:[
+        ^ nanosFromMillis + (FixedPoint numerator:additionalPicoseconds denominator:(1000) scale:3)
+    ].
+    ^ nanosFromMillis.
+
+    "
+     |ts|
+
+     ts := Timestamp now + 100.3 nanoseconds.
+     Transcript showCR:ts.
+     Transcript showCR:ts milliseconds.
+     Transcript showCR:ts exactMilliseconds.
+     Transcript showCR:ts microseconds.
+     Transcript showCR:ts exactMicroseconds.
+     Transcript showCR:ts nanoseconds.
+     Transcript showCR:ts exactNanoseconds.
+     Transcript showCR:ts picoseconds.
+    "
+!
+
+exactSeconds
+    "return the exact seconds within the stamp's minute (00 .. 59.999...) as a fixedPoint number.
+     Notice: 
+        that is NOT the total number of seconds,
+        but the fractional part (within the minute) only.
+     A fixedPoint number holds the exact value, but prints itself rounded!!"
+
+    |seconds additionalSeconds|
+
+    seconds := FixedPoint numerator:(osTime \\ (60*1000)) denominator:1000 scale:3.
+    additionalPicoseconds notNil ifTrue:[
+        additionalSeconds := (FixedPoint numerator:additionalPicoseconds denominator:(1000*1000*1000*1000) scale:3).
+        seconds := seconds + additionalSeconds
+    ].
+    ^ seconds.
+
+    "
+     |ts|
+
+     ts := Timestamp fromDate:(Date today) hour:10 minute:30 second:20 millisecond:300.
+     Transcript showCR:ts.
+     Transcript showCR:ts seconds.
+     Transcript showCR:ts exactSeconds.
+    "
 !
 
 hours
@@ -1836,8 +2233,47 @@
     "Modified: 2.7.1996 / 09:20:32 / cg"
 !
 
+microseconds
+    "return the truncated microseconds within the stamp's second (0..999999).
+     notice: that is NOT the total number of microseconds,
+     but the fractional part (within the second) only. 
+     Use this only for printing."
+
+    |millis microsFromMillis|
+
+    millis := (osTime \\ 1000).
+    microsFromMillis := millis * 1000.
+    additionalPicoseconds notNil ifTrue:[
+        ^ microsFromMillis + (additionalPicoseconds // (1000*1000))
+    ].
+    ^ microsFromMillis.
+
+    "
+     -- (definitely millisecond resolution here)
+     Timestamp now                          
+     Timestamp now microseconds             
+
+     -- (but some OS's only deliver millisecond resolution also here)
+     Timestamp nowWithMicroseconds microseconds
+
+
+     |t1 t2|
+     t1 := Timestamp nowWithMicroseconds microseconds.
+     t2 := Timestamp nowWithMicroseconds microseconds.
+     t2-t1
+
+     |t1 t2|
+     t1 := Timestamp now microseconds.
+     t2 := Timestamp nowWithMicroseconds microseconds.
+     t2-t1
+    "
+
+    "Created: 1.7.1996 / 15:15:02 / cg"
+    "Modified: 2.7.1996 / 09:21:41 / cg"
+!
+
 millisecond
-    "return the millisecond (0..999).
+    "return the truncated millisecond within the stamp's second (0..999).
      ST-80 Timestamp compatibility (I'd prefer the name #milliseconds)."
 
     ^ self milliseconds
@@ -1847,10 +2283,9 @@
 !
 
 milliseconds
-    "return the milliseconds (0..999)"
+    "return the truncated milliseconds within the stamp's second (0..999)"
 
     ^ osTime \\ 1000.
-"/    ^ self timeInfo milliseconds
 
     "
      Timestamp now milliseconds
@@ -1860,16 +2295,6 @@
     "Modified: 2.7.1996 / 09:21:41 / cg"
 !
 
-minute
-    "return the minute (0..59).
-     ST-80 Timestamp compatibility (I'd prefer the name #minutes, for Time compatibility)."
-
-    ^ self minutes
-
-    "Created: 1.7.1996 / 15:14:29 / cg"
-    "Modified: 1.7.1996 / 15:15:37 / cg"
-!
-
 minutes
     "return the minutes (0..59)"
 
@@ -1912,6 +2337,39 @@
     "
 !
 
+nanoseconds
+    "return the truncated nanoseconds within the stamp's second (0..999999999).
+     notice: that is NOT the total number of nanoseconds,
+     but the fractional part (within the second) only. 
+     Use this only for printing."
+
+    |nanosFromMillis|
+
+    nanosFromMillis := (osTime \\ 1000) * (1000 * 1000).
+    additionalPicoseconds notNil ifTrue:[
+        ^ nanosFromMillis + (additionalPicoseconds // 1000)
+    ].
+    ^ nanosFromMillis.
+
+    "
+     Timestamp now nanoseconds
+     Timestamp nowWithMicroseconds nanoseconds
+
+     |t1 t2|
+     t1 := Timestamp nowWithMicroseconds nanoseconds.
+     t2 := Timestamp nowWithMicroseconds nanoseconds.
+     t2-t1
+
+     |t1 t2|
+     t1 := Timestamp now nanoseconds.
+     t2 := Timestamp nowWithMicroseconds nanoseconds.
+     t2-t1
+    "
+
+    "Created: 1.7.1996 / 15:15:02 / cg"
+    "Modified: 2.7.1996 / 09:21:41 / cg"
+!
+
 osTime
     "get the internal representation of the time.
      Warning: do not depend on the value (unix vs. win32 - differences)"
@@ -1919,27 +2377,28 @@
     ^ osTime
 !
 
-osTime:aTime
-    "set the internal representation of the time"
-
-    osTime := aTime.
-!
-
-second
-    "return the second (0..59).
-     ST-80 Timestamp compatibility (I'd prefer the name #seconds, for Time compatibility)."
-
-    ^ self seconds
-
-    "Created: 1.7.1996 / 15:14:19 / cg"
-    "Modified: 1.7.1996 / 15:15:49 / cg"
+picoseconds
+    "return the picoseconds within the stamp's second (0..999999999999).
+     notice: that is NOT the total number of picoseconds,
+     but the fractional part (within the second) only. 
+     Use this only for printing."
+
+    |picosFromMillis|
+
+    picosFromMillis := (osTime \\ 1000) * (1000 * 1000 * 1000).
+    ^ picosFromMillis + (additionalPicoseconds ? 0)
+
+    "
+     Timestamp now picoseconds
+     Timestamp nowWithMicroseconds picoseconds
+    "
 !
 
 seconds
-    "return the seconds (0..59)"
+    "return the truncated seconds (0..59)"
 
     (osTime between:MinOSTime and:MaxOSTime) ifFalse:[
-	^ self asTime seconds.
+        ^ self asTime seconds.
     ].
     ^ self timeInfo seconds
 
@@ -2012,14 +2471,14 @@
      Add utcOffset to convert from local time to UTC time.
      Subtract utcOffset to convert from UTC time to local time.
 
-     If utcOffset is negative, the local timezone is east of Greenwich.
-     If utcOffset is positive, the local timezone is west of Greenwich."
+     If utcOffset is negative, the local timezone is east of Greenwich (Russia, Asia).
+     If utcOffset is positive, the local timezone is west of Greenwich (USA)."
 
     (osTime between:MinOSTime and:MaxOSTime) ifFalse:[
-	"/ fake an info which the OS cannot give me
-	"/ we do not know about DST in the far future and in the long gone past.
-	"/ Take the utcOffset without DST
-	^ self utcOffsetWithoutDst.
+        "/ fake an info which the OS cannot give me
+        "/ we do not know about DST in the far future and in the long gone past.
+        "/ Take the utcOffset without DST
+        ^ self utcOffsetWithoutDst.
     ].
 
     ^ (OperatingSystem computeTimeAndDateFrom:osTime) utcOffset
@@ -2146,12 +2605,32 @@
     "Created: / 08-01-2011 / 16:20:55 / cg"
 !
 
-millisecondDeltaFrom:aTimestamp
-    "return the delta in milliseconds between 2 absolute times.
+microsecondDeltaFrom:aTimestamp
+    "return the delta in (truncated) microseconds between 2 timestamps.
      The argument is supposed to be BEFORE the receiver,
-	computes self - aTimestamp"
-
-    ^ self getMilliseconds - (aTimestamp getMilliseconds)
+        computes self - aTimestamp"
+
+    ^ self getMicroseconds - (aTimestamp getMicroseconds)
+
+    "
+     |t1 t2|
+
+     t1 := Timestamp now.
+     Delay waitForSeconds:0.5.
+     t2 := Timestamp now.
+     t2 microsecondDeltaFrom:t1
+    "
+
+    "Modified: / 10-07-2010 / 09:37:18 / cg"
+    "Modified (comment): / 26-02-2019 / 14:02:16 / Claus Gittinger"
+!
+
+millisecondDeltaFrom:aTimestamp
+    "return the delta in (truncated) milliseconds between 2 timestamps.
+     The argument is supposed to be BEFORE the receiver,
+        computes self - aTimestamp"
+
+    ^ osTime - (aTimestamp getMilliseconds)
 
     "
      |t1 t2|
@@ -2163,6 +2642,8 @@
     "
 
     "Modified: / 10-07-2010 / 09:37:18 / cg"
+    "Modified: / 27-07-2018 / 10:34:11 / Stefan Vogel"
+    "Modified (comment): / 26-02-2019 / 14:02:13 / Claus Gittinger"
 !
 
 roundedToSecond
@@ -2185,9 +2666,9 @@
 !
 
 secondDeltaFrom:aTimestamp
-    "return the delta in seconds between 2 absolute times.
+    "return the delta in (truncated) seconds between 2 timestamps.
      The argument is supposed to be BEFORE the receiver,
-	computes self - aTimestamp"
+        computes self - aTimestamp"
 
     ^ self getSeconds - (aTimestamp getSeconds)
 
@@ -2201,25 +2682,15 @@
     "
 
     "Modified: / 10-07-2010 / 09:37:24 / cg"
+    "Modified (comment): / 26-02-2019 / 14:02:09 / Claus Gittinger"
 ! !
 
 !Timestamp methodsFor:'comparing'!
 
-= aTimestamp
-    "return true if the argument, aTime represents the same time.
-     Notice: you can compare timestamps from different timezones for representing the
-     same time, because they all store their milliseconds internally as utc time"
-
-    aTimestamp isTimestamp ifFalse:[^ false].
-    ^ (self getMilliseconds = aTimestamp getMilliseconds)
-
-    "Modified: 3.7.1996 / 13:10:24 / cg"
-!
-
 hash
-    "return an integer useful for hashing on times"
-
-    ^ osTime // 1000
+    "return an integer useful for hashing on time stamps"
+
+    ^ osTime "// 1000" - why ignore the millis?
 
     "Modified: 3.7.1996 / 13:10:52 / cg"
 ! !
@@ -2272,10 +2743,14 @@
     ^ self asTZTimestamp:self utcOffset
 
     "see the different printStrings of:
-	 Timestamp now
+         Timestamp now
+     and
+         Timestamp now asTZTimestamp
      and
-	 Timestamp now asTZTimestamp
-    "
+         Timestamp now asUtcTimestamp
+    "
+
+    "Modified (comment): / 24-05-2018 / 17:31:26 / Claus Gittinger"
 !
 
 asTZTimestamp:utcOffset
@@ -2419,22 +2894,29 @@
     "
 !
 
-utcOffset:anOffset
-   "answer a DateTime equivalent to the receiver but offset from UTC by offset"
+utcOffset:secondsOrTimeDuration
+   "answer a DateTime equivalent to the receiver but offset from UTC by offset.
+     If utcOffset is negative, the local timezone is east of Greenwich (Russia, Asia).
+     If utcOffset is positive, the local timezone is west of Greenwich (USA).
+     If utcOffset is zero, you effectively get UTC time."
 
     ^ TZTimestamp new 
         osTime:osTime;
-        utcOffset:(anOffset asTimeDuration)  
+        utcOffset:(secondsOrTimeDuration asTimeDuration);
+        yourself.
 
     "
      Timestamp now  -- now as local time
      Timestamp now asTZTimestamp -- now in your local timezone
      Timestamp now asUtcTimestamp -- now in greenwich
      UtcTimestamp now -- now in greenwich
-     Timestamp now utcOffset:(-2 hours)2015-11-09 17:29:35.803+02 -- now in East Europe
+     Timestamp now utcOffset:(-2 hours) -- now in East Europe
      Timestamp now utcOffset:(5 hours) -- now in Eastern time
      Timestamp now asTZTimestampInZone:'EST' -- now in Eastern time
     "
+
+    "Modified: / 27-07-2018 / 11:54:45 / Stefan Vogel"
+    "Modified: / 26-05-2019 / 12:54:56 / Claus Gittinger"
 !
 
 utcSecondsSince1901
@@ -2442,8 +2924,8 @@
 
 "
     secondsBetween1901and1970 :=
-	((Date day:1 month:1 year:1970) subtractDate:(Date day:1 month:1 year:1901))
-	*  (24 * 60 * 60)
+        ((Date year:1970 month:1 day:1) subtractDate:(Date year:1901  month:1 day:1))
+        *  (24 * 60 * 60)
 "
 
     ^ self utcSecondsSince1970 + 2177452800.
@@ -2451,17 +2933,44 @@
     "
      Timestamp now utcSecondsSince1901
     "
+
+    "Modified (comment): / 10-12-2018 / 20:37:38 / Stefan Vogel"
+! !
+
+!Timestamp methodsFor:'double dispatching'!
+
+differenceFromTimestamp:aTimestamp
+    |newMillis newPicos|
+
+    newMillis := aTimestamp getMilliseconds - osTime.
+    newPicos := (aTimestamp additionalPicoseconds) - (additionalPicoseconds ? 0).
+
+    ^ TimeDuration basicNew
+        setMilliseconds:newMillis additionalPicoseconds:newPicos.
+
+    "Created: / 27-07-2018 / 08:45:22 / Stefan Vogel"
+    "Modified (format): / 27-07-2018 / 10:50:05 / Stefan Vogel"
 ! !
 
 !Timestamp methodsFor:'initialization'!
 
 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."
+     given y,m,d and h,m,s in my time.
+     All arguments MUST be integral (for now)"
 
     self setOSTimeFromUTCYear: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 additionalPicoseconds:picos
+    "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.
+     All arguments MUST be integral (for now)"
+
+    self setOSTimeFromUTCYear:y month:m day:d hour:h minute:min second:s millisecond:millis.
+    additionalPicoseconds := picos.
+!
+
 setOSTimeFromUTCYear: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"
@@ -2515,7 +3024,8 @@
 
 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."
+     given y,m,d and h,m,s in my time.
+     All arguments MUST be integral (for now)"
 
     self setOSTimeFromYear:y month:m day:d hour:h minute:min second:s millisecond:millis
 
@@ -2523,9 +3033,22 @@
      self basicNew
          year:2016 month:4 day:16 hour:17 minute:21 second:13 millisecond:726
     "
+!
+
+year:y month:m day:d hour:h minute:min second:s millisecond:millis additionalPicoseconds:picos
+    "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.
+     All arguments MUST be integral (for now)"
+
+    self setOSTimeFromYear:y month:m day:d hour:h minute:min second:s millisecond:millis.
+    additionalPicoseconds := picos
+
+    "
+     self basicNew
+         year:2016 month:4 day:16 hour:17 minute:21 second:13 millisecond:726
+    "
 ! !
 
-
 !Timestamp methodsFor:'printing & storing'!
 
 addPrintBindingsTo:dict language:languageOrNil
@@ -2550,9 +3073,11 @@
     "
     
     "used by:
-        Timestamp now printStringFormat:'%y-%m-%d'
+        Timestamp now printStringFormat:'%y-%(mon)-%d'
         Timestamp now printStringFormat:'%(dayOfYear)'
     "
+
+    "Modified (comment): / 03-11-2017 / 10:54:30 / cg"
 !
 
 printGeneralizedOn:aStream
@@ -2654,17 +3179,22 @@
 !
 
 printISO8601
+    "obsoleted due to uc/lc and print vs. printString confusion"
+
     <resource: #obsolete>
-    "print as UTC in a format like 2014-10-17T17:08:44Z"
+    "print in a format like 2014-10-17T17:08:44Z"
 
     ^ self printStringIso8601
 
     "Created: / 16-06-2005 / 16:11:15 / masca"
+    "Modified (comment): / 25-05-2018 / 12:00:52 / Claus Gittinger"
 !
 
 printISO8601Compressed
+    "obsoleted due to uc/lc and print vs. printString confusion"
+
     <resource: #obsolete>
-    "return a printString as UTC in a format like 20141017T170939Z"
+    "return a printString in a format like 20141017T170939Z"
 
     ^ self printStringIso8601Compressed
 
@@ -2673,45 +3203,55 @@
     "
 
     "Created: / 16-06-2005 / 16:11:31 / masca"
+    "Modified (comment): / 25-05-2018 / 12:00:47 / Claus Gittinger"
 !
 
 printISO8601CompressedOn: aStream
+    "obsoleted due to uc/lc confusion"
+
     <resource: #obsolete>
-    "print as UTC in a format like 20141017T170939Z on aStream"
+    "print in a format like 20141017T170939Z on aStream"
 
     self printIso8601CompressedOn: aStream
 
     "Created: / 16-06-2005 / 16:11:50 / masca"
+    "Modified (comment): / 25-05-2018 / 12:00:42 / Claus Gittinger"
 !
 
 printISO8601On: aStream
+    "obsoleted due to uc/lc confusion"
+
     <resource: #obsolete>
-    "print as UTC in a format like 2014-10-17T17:08:44Z on aStream"
+    "print in a format like 2014-10-17T17:08:44Z on aStream"
 
     self printIso8601On: aStream
 
     "Created: / 16-06-2005 / 16:11:07 / masca"
+    "Modified (comment): / 25-05-2018 / 12:00:37 / Claus Gittinger"
 !
 
 printIso8601CompressedOn: aStream
-    "print as UTC in a format like 20141017T170939Z on aStream"
-
-    TimestampISO8601Builder printCompressed: self on: aStream
+    "print in a format like 20141017T170939Z on aStream"
+
+    self printIso8601FormatOn:aStream compressed:true timeSeparator:$T
 
     "Created: / 16-06-2005 / 16:11:50 / masca"
+    "Modified: / 24-05-2018 / 17:33:12 / Claus Gittinger"
+    "Modified (comment): / 25-05-2018 / 12:00:30 / Claus Gittinger"
 !
 
 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."
-
-    self printIso8601FormatOn:aStream timeSeparator:$T
+     Timezone information (eg. Z or +0100) is added for TZ and Utc stamps, 
+     otherwise the reader will read as local time."
+
+    self printIso8601FormatOn:aStream compressed:false timeSeparator:$T
 
     "
      Timestamp now printIso8601FormatOn:Transcript. Transcript cr.
@@ -2720,35 +3260,36 @@
      UtcTimestamp now printIso8601FormatOn:Transcript. Transcript cr.
      UtcTimestamp readIso8601FormatFrom:(UtcTimestamp now printStringIso8601Format).
     "
+
+    "Modified: / 24-05-2018 / 17:28:36 / Claus Gittinger"
+    "Modified (comment): / 25-05-2018 / 12:00:23 / Claus Gittinger"
 !
 
-printIso8601FormatOn:aStream timeSeparator:sepChar
+printIso8601FormatOn:aStream compressed:compact timeSeparator:sepChar
     "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."
+     Timezone information (eg. Z or +0100) is added for TZ and Utc stamps, 
+     otherwise the reader will read as local time."
 
     |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.
-	]
+        asUTC := false.
+        asLocal := self isLocalTimestamp.
     ].
 
     Timestamp::TimestampISO8601Builder
-	print:self compact:false
-	asLocal:asLocal asUTC:asUTC withMilliseconds:true
-	timeSeparator:sepChar
-	on:aStream
+        print:self compact:compact
+        asLocal:asLocal asUTC:asUTC withMilliseconds:true
+        timeSeparator:sepChar
+        on:aStream
 
 "/
 "/    |format|
@@ -2766,20 +3307,54 @@
 "/    self printOn:aStream format:format
 
     "
+     Timestamp now printStringIso8601Format.
+
      Timestamp now printIso8601FormatOn:Transcript. Transcript cr.
      Timestamp readIso8601FormatFrom:(Timestamp now printStringIso8601Format).
 
      UtcTimestamp now printIso8601FormatOn:Transcript. Transcript cr.
      UtcTimestamp readIso8601FormatFrom:(UtcTimestamp now printStringIso8601Format).
     "
+
+    "Created: / 24-05-2018 / 17:28:25 / Claus Gittinger"
+    "Modified (comment): / 25-05-2018 / 12:00:14 / Claus Gittinger"
+    "Modified: / 27-07-2018 / 11:57:21 / Stefan Vogel"
+!
+
+printIso8601FormatOn:aStream timeSeparator:sepChar
+    "append the iso8601 representation of the receiver to aStream.
+     This format looks like:
+        1999-01-01T24:00:00
+     or, for zero hr:min:sec,
+        1999-01-01
+     Of course, a 24 hour clock is used.
+
+     Timezone information (eg. Z or +0100) is added for TZ and Utc stamps, 
+     otherwise, the reader will read as local time."
+
+    self printIso8601FormatOn:aStream compressed:false timeSeparator:sepChar
+
+    "
+     Timestamp now printStringIso8601Format.
+
+     Timestamp now printIso8601FormatOn:Transcript. Transcript cr.
+     Timestamp readIso8601FormatFrom:(Timestamp now printStringIso8601Format).
+
+     UtcTimestamp now printIso8601FormatOn:Transcript. Transcript cr.
+     UtcTimestamp readIso8601FormatFrom:(UtcTimestamp now printStringIso8601Format).
+    "
+
+    "Modified: / 24-05-2018 / 17:28:28 / Claus Gittinger"
+    "Modified (comment): / 25-05-2018 / 11:59:57 / Claus Gittinger"
 !
 
 printIso8601On: aStream
-    "print as UTC in a format like 2014-10-17T17:08:44Z on aStream"
+    "print in a format like 2014-10-17T17:08:44Z on aStream"
 
     TimestampISO8601Builder print: self on: aStream
 
     "Created: / 16-06-2005 / 16:11:07 / masca"
+    "Modified (comment): / 25-05-2018 / 11:59:22 / Claus Gittinger"
 !
 
 printOn:aStream
@@ -2789,20 +3364,16 @@
     |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.
-	]
+        asLocal := self isLocalTimestamp.
     ].
 
     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'
@@ -2831,7 +3402,8 @@
      Date today printOn:Transcript. Transcript cr.
     "
 
-    "Modified: 1.7.1996 / 15:20:59 / cg"
+    "Modified: / 01-07-1996 / 15:20:59 / cg"
+    "Modified: / 27-07-2018 / 11:58:58 / Stefan Vogel"
 !
 
 printRFC1123FormatOn:aStream
@@ -2894,45 +3466,6 @@
     "
 !
 
-printStringIso8601
-    "return a printString as UTC in a format like 2014-10-17T17:08:44Z"
-
-    ^ TimestampISO8601Builder print: self
-
-    "
-     Timestamp now printStringIso8601
-    "
-
-    "Created: / 16-06-2005 / 16:11:15 / masca"
-!
-
-printStringIso8601Compressed
-    "return a printString as UTC in a format like 20141017T170939Z"
-
-    ^ TimestampISO8601Builder printCompressed: self
-
-    "
-     Timestamp now printStringIso8601Compressed
-    "
-
-    "Created: / 16-06-2005 / 16:11:31 / masca"
-!
-
-printStringIso8601Format
-    "return the Iso8601 representation of the receiver with local timezon information.
-     This format looks like:
-	1999-01-01T24:00:00
-     or, for zero hr:min:sec,
-	1999-01-01
-     Of course, a 24 hour clock is used."
-
-    ^ String streamContents:[:s | self printIso8601FormatOn:s]
-
-    "
-     Timestamp now printStringIso8601Format
-    "
-!
-
 printStringRFC1123Format
     "return the RFC1123 representation of the receiver.
      This format is used in HTTP requests and looks like:
@@ -2966,11 +3499,45 @@
 !
 
 storeStringClass
+    "my storeString will ask Timestamp to read the instance"
+
     ^ self class
 ! !
 
 !Timestamp methodsFor:'private'!
 
+additionalPicoseconds
+    "return the additional picoseconds (0..999999999).
+     These must alwyas be smaller than 1000*1000*1000 (i.e. 1ms),
+     to avoid overflow into the millis.
+     These are to be added to any milliseconds"
+
+    ^ additionalPicoseconds ? 0.
+
+    "
+     Timestamp now picoseconds
+     Timestamp nowWithMicroseconds picoseconds
+    "
+!
+
+additionalPicoseconds:anInteger
+    "set the additional picoseconds (0..999999999).
+     These must alwyas be smaller than 1000*1000*1000 (i.e. 1ms),
+     to avoid overflow into the millis."
+
+    self assert:(anInteger isInteger).
+    self assert:(anInteger < (1000*1000*1000)).
+    additionalPicoseconds:= anInteger
+
+    "
+     Timestamp now picoseconds
+     Timestamp now additionalPicoseconds
+
+     Timestamp nowWithMicroseconds picoseconds
+     Timestamp nowWithMicroseconds additionalPicoseconds
+    "
+!
+
 computeTimeInfo
     |d t info|
 
@@ -3019,13 +3586,39 @@
 !
 
 fromOSTimeWithMilliseconds:anUninterpretedOSTime
-    "strictly private: set the milliseconds from an OS time (since the epoch)"
+    "strictly private: set the milliseconds from an OS time (since the epoch).
+     Notice: timestamps always have millisecond precision (in contrast to Time, where it is optional)"
 
     osTime := anUninterpretedOSTime
 !
 
+fromOSTimeWithMilliseconds:anUninterpretedOSTime additionalPicoseconds:picos
+    "strictly private: set the milliseconds and picoSeconds from an OS time (since the epoch)"
+
+    osTime := anUninterpretedOSTime.
+    additionalPicoseconds := picos
+
+    "
+     Timestamp nowWithMicroseconds
+    "
+!
+
+getMicroseconds
+    "strictly private: return the truncated microseconds (since the epoch) in utc"
+
+    |millisAsMicros|
+
+    millisAsMicros := osTime * 1000.
+    additionalPicoseconds notNil ifTrue:[
+        ^ millisAsMicros + (additionalPicoseconds // (1000 * 1000)).   
+    ].
+    ^ millisAsMicros
+
+    "Created: 1.7.1996 / 14:33:56 / cg"
+!
+
 getMilliseconds
-    "strictly private: return the milliseconds (since the epoch) in utc"
+    "strictly private: return the truncated milliseconds (since the epoch) in utc"
 
     ^ osTime
 
@@ -3033,9 +3626,47 @@
 !
 
 getSeconds
-    "strictly private: return the seconds (since the epoch) in utc"
+    "strictly private: return the (truncated) seconds (since the epoch) in utc"
 
     ^ osTime // 1000
+
+    "Modified (comment): / 21-09-2017 / 18:50:23 / cg"
+!
+
+osTime:aTime
+    "set the internal representation of the time"
+
+    osTime := aTime.
+!
+
+setMicrosecond:aNumber
+    "change the sub-second fractional part only (leaves everything above seconds unchanged)"
+
+    self 
+        setMilliseconds:(osTime // 1000) * 1000   "/ strip off any sub-second part 
+        additionalPicoseconds:(aNumber * 1000000) truncated.    "/ set picos 
+
+    "
+     Timestamp now setMicrosecond:15    - 15 microseconds after the current second's start 
+     Timestamp now setMicrosecond:0.1   - 100 nanoseconds after the current second's start 
+    "
+
+    "Modified: / 27-07-2018 / 10:34:18 / Stefan Vogel"
+!
+
+setMillisecond:aNumber
+    "change the sub-second fractional part only (leaves everything above seconds unchanged)"
+
+    self 
+        setMilliseconds:(osTime // 1000) * 1000       "/ strip off any sub-second part 
+        additionalPicoseconds:(aNumber * 1000000000) truncated.     "/ set picos 
+
+    "
+     Timestamp now setMillisecond:15    - 15 milliseconds after the current second's start
+     Timestamp now setMillisecond:0.05  - 50 microseconds after the current second's start
+    "
+
+    "Modified: / 27-07-2018 / 10:34:42 / Stefan Vogel"
 !
 
 setMilliseconds:millis
@@ -3047,6 +3678,46 @@
     "Created: 1.7.1996 / 14:34:24 / cg"
 !
 
+setMilliseconds:millis additionalPicoseconds:picos
+    "strictly private: set the milliseconds (since the epoch) and additional picos"
+
+    |rest newMillis newPicos|
+
+    millis isInteger ifTrue:[
+        newMillis := millis.
+        newPicos := 0.
+    ] ifFalse:[
+        newMillis := millis truncated.
+        rest := millis - newMillis.
+        newPicos := (rest * 1000000000) truncated.
+    ].
+
+    picos ~~ 0 ifTrue:[
+        newPicos := newPicos + picos.
+        newMillis := newMillis + (newPicos // 1000000000).
+        newPicos := (newPicos \\ 1000000000) truncated.
+    ].
+    osTime := newMillis.
+    additionalPicoseconds := newPicos.
+
+    "Modified: / 22-05-2018 / 16:50:34 / Stefan Vogel"
+!
+
+setNanosecond:aNumber
+    "change the sub-second fractional part only (leaves everything above seconds unchanged)"
+
+    self 
+        setMilliseconds:(osTime // 1000) * 1000   "/ strip off any sub-second part
+        additionalPicoseconds:(aNumber * 1000) rounded.         "/ set picos
+
+    "
+     Timestamp now setNanosecond:15     - 15 nanoseconds after the current second's start
+     Timestamp now setNanosecond:0.1    - 10 picoseconds after the current second's start
+    "
+
+    "Modified: / 27-07-2018 / 10:34:52 / Stefan Vogel"
+!
+
 setSeconds:secs
     "strictly private: set the seconds (since whatever)"
 
@@ -3094,14 +3765,31 @@
     "
 ! !
 
-
+!Timestamp methodsFor:'queries'!
+
+speciesForCompare
+    "all of my subclass instances can be compared,
+     because they all hold the UTC time internally"
+     
+    ^ Timestamp
+! !
 
 !Timestamp methodsFor:'testing'!
 
 isLocalTimestamp
-    "return true, if I am a local timestamp"
+    "return true, if I am a local timestamp (i.e. with no TZ info)"
 
     ^ true
+
+    "Modified (comment): / 24-05-2018 / 17:29:32 / Claus Gittinger"
+!
+
+isTZTimestamp
+    "return true, if I am a timestamp with TZ info"
+
+    ^ false
+
+    "Created: / 24-05-2018 / 17:30:25 / Claus Gittinger"
 !
 
 isTimestamp
@@ -3124,6 +3812,14 @@
     ^ aVisitor visitTimestamp:self with:aParameter
 ! !
 
+!Timestamp::TimestampBuilderAbstract class methodsFor:'documentation'!
+
+documentation
+"
+    abstract timestamp reader support
+"
+! !
+
 !Timestamp::TimestampBuilderAbstract methodsFor:'error reporting'!
 
 malformed:aString
@@ -3190,6 +3886,16 @@
     "Modified: / 16-06-2005 / 15:04:45 / masca"
 !
 
+dateAlreadyReadAs:date
+    "support for readers which may have already preread the date"
+
+    year := date year.
+    yearAlreadyRead := true.
+    month := date month.
+    day := date day.
+    millisecond := second := minute := hour := picos := 0.
+!
+
 dateFromDayNumber: dayInYear
     "Set month and day from an absolute number of the day in the year. 1.1. is day number one."
 
@@ -3208,9 +3914,10 @@
     "Modified: / 16-06-2005 / 12:31:37 / masca"
 !
 
-dateFromWeek: weekInteger andWeekday: dayInteger
-    "Compute the month and day. Find the first day (weekday) in the year, maybe even
-    adjust the year. Both week and day are 1-based, the first week in a year is the one
+dateFromWeek:weekInteger andWeekday:dayInteger
+    "Compute the week and weekDay. 
+    Find the first day (weekday) in the year, maybe even adjust the year. 
+    Both week and day are 1-based, the first week in a year is the one
     with thursday (or the one containing 4.1.)."
 
     |tmpDate|
@@ -3255,32 +3962,34 @@
      Attention: an explicit utcOffset in the input string has already been added into the hh:mm values."
 
     (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 additionalPicoseconds:picos
     ].
     (timestampClass == TZTimestamp) ifTrue:[
-	"/ Attention: an explicit utcOffset in the input string has already been added into the hh:mm values."
-	^ ((TZTimestamp
-	    UTCYear: year month: month day: day
-	    hour: hour minute: minute second: second millisecond: millisecond) utcOffset:utcOffset)
+        "/ Attention: an explicit utcOffset in the input string has already been added into the hh:mm values."
+        ^ ((TZTimestamp
+            UTCYear:year month:month day:day
+            hour:hour minute:minute second:second millisecond:millisecond additionalPicoseconds:picos
+           ) 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 additionalPicoseconds:picos
     ].
     hasTimezone ifTrue:[
-	"/ Attention: an explicit utcOffset in the input string has already been added into the hh:mm values."
-	^ (((timestampClass == Timestamp) ifTrue:TZTimestamp ifFalse:timestampClass)
-	    UTCYear: year month: month day: day
-	    hour: hour minute: minute second: second millisecond: millisecond) utcOffset:utcOffset
+        "/ Attention: an explicit utcOffset in the input string has already been added into the hh:mm values."
+        ^ (((timestampClass == Timestamp) ifTrue:TZTimestamp ifFalse:timestampClass)
+            UTCYear:year month:month day:day
+            hour:hour minute:minute second:second millisecond:millisecond additionalPicoseconds:picos
+          ) utcOffset:utcOffset
     ].
     "/ there was no timezone info, so make it a local timestamp again.
-    ^ (timestampClass
-	year: year month: month day: day
-	hour: hour minute: minute second: second millisecond: millisecond)
+    ^ timestampClass
+        year:year month:month day:day
+        hour:hour minute:minute second:second millisecond:millisecond additionalPicoseconds:picos
 !
 
 yearAlreadyReadAs:yearArg
@@ -3329,14 +4038,14 @@
 
 examples
 "
-    See the unit tests in exept:regression >> RegressionTests::timeAndDateTest
+    See the unit tests in stx/goodies:regression >> RegressionTests::timeAndDateTest
     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: TZTimestamp now)
+        Timestamp readISO8601From: (TimestampISO8601Builder print: Timestamp now).
+        UtcTimestamp readISO8601From: (TimestampISO8601Builder print: UtcTimestamp now).
+        Timestamp readISO8601From: (TimestampISO8601Builder print: UtcTimestamp now).
+        Timestamp readISO8601From: (TimestampISO8601Builder print: TZTimestamp now).
 
     Timestamp readISO8601From:'fooBar' onError:[ Timestamp now ].
 "
@@ -3385,10 +4094,19 @@
      such as '2014-11-06T11:48:09Z'.
      The time is printed as UTC time"
 
-    self print:aTimestamp compact:false asLocal:false asUTC:true withMilliseconds:true on:aStream
-
-    "
-     self print:(Timestamp now) on:Transcript
+    self 
+        print:aTimestamp 
+        compact:false asLocal:false asUTC:true 
+        withMilliseconds:true timeSeparator:$T timeOnly:false
+        on:aStream
+
+    "
+     self print:(Timestamp now) on:Transcript.
+     Transcript cr.
+     self print:(Time now) on:Transcript.
+     Transcript cr.
+     self print:(Time nowWithMilliseconds) on:Transcript.
+     Transcript cr.
     "
 
     "Created: / 15-06-2005 / 17:56:51 / masca"
@@ -3399,7 +4117,10 @@
      such as '2014-11-06T11:48:09+01'.
      The time is printed as local time"
 
-    self print:aTimestamp compact:false asLocal:true asUTC:false withMilliseconds:true on:aStream
+    self 
+        print:aTimestamp compact:false asLocal:true asUTC:false 
+        withMilliseconds:true timeSeparator:$T timeOnly:false 
+        on:aStream
 
     "
      self printAsLocalTime:(Timestamp now) on:Transcript
@@ -3424,10 +4145,32 @@
     "Created: / 15-06-2005 / 17:52:52 / masca"
 !
 
-printCompressed:aTimestamp asLocal:asLocal on: aStream
-    "generates a compressed string representation, such as '20141106T114636Z'"
-
-    self print:aTimestamp compact:true asLocal:asLocal asUTC:asLocal not withMilliseconds:true on:aStream
+printCompressed:aTimestamp asLocal:asLocal on:aStream
+    "generates a compressed string representation, 
+     (optionally as localtime) such as '20141106T114636Z'"
+
+    self 
+        print:aTimestamp 
+        compact:true asLocal:asLocal asUTC:asLocal not 
+        withMilliseconds:true timeSeparator:$T timeOnly:false
+        on:aStream
+
+    "
+     self printCompressed:(Timestamp now) on:Transcript
+    "
+
+    "Created: / 15-06-2005 / 17:54:17 / masca"
+!
+
+printCompressed:aTimestamp on:aStream
+    "generates a compressed string representation, such as '20141106T114636Z'.
+     The time is printed as UTC time"
+
+    self 
+        print:aTimestamp 
+        compact:true asLocal:false asUTC:true 
+        withMilliseconds:true timeSeparator:$T timeOnly:false 
+        on:aStream
 
     "
      self printCompressed:(Timestamp now) on:Transcript
@@ -3436,11 +4179,15 @@
     "Created: / 15-06-2005 / 17:54:17 / masca"
 !
 
-printCompressed: aTimestamp on: aStream
+printCompressedAsLocalTime:aTimestamp on:aStream
     "generates a compressed string representation, such as '20141106T114636Z'.
-     The time is printed as UTC time"
-
-    self print:aTimestamp compact:true asLocal:false asUTC:true withMilliseconds:true on:aStream
+     The time is printed as local time"
+
+    self 
+        print:aTimestamp 
+        compact:true asLocal:true asUTC:false 
+        withMilliseconds:true timeSeparator:$T timeOnly:false 
+        on:aStream
 
     "
      self printCompressed:(Timestamp now) on:Transcript
@@ -3449,17 +4196,26 @@
     "Created: / 15-06-2005 / 17:54:17 / masca"
 !
 
-printCompressedAsLocalTime: aTimestamp on: aStream
-    "generates a compressed string representation, such as '20141106T114636Z'.
-     The time is printed as local time"
-
-    self print:aTimestamp compact:true asLocal:true asUTC:false withMilliseconds:true on:aStream
-
-    "
-     self printCompressed:(Timestamp now) on:Transcript
-    "
-
-    "Created: / 15-06-2005 / 17:54:17 / masca"
+printTime:aTimeOrTimestamp on:aStream
+    "Print the given time in general ISO8601 format,
+     such as 'T11:48:09Z'.
+     The time is printed as UTC time.
+     No date is printed."
+
+    self 
+        print:aTimeOrTimestamp 
+        compact:false asLocal:false asUTC:true 
+        withMilliseconds:true timeSeparator:$T timeOnly:true
+        on:aStream
+
+    "
+     self print:(Time nowWithMilliseconds) on:Transcript.
+     Transcript cr.
+     self printTime:(Time nowWithMilliseconds) on:Transcript.
+     Transcript cr.
+    "
+
+    "Created: / 15-06-2005 / 17:56:51 / masca"
 !
 
 printTimeZone:tzOffsetArg on: aStream
@@ -3509,31 +4265,168 @@
 
 !Timestamp::TimestampISO8601Builder class methodsFor:'printing - basic'!
 
+print:aTimeOrTimestamp compact:compact asLocal:asLocal asUTC:asUTC 
+    subSecondDigits:numDigits
+    suppressZeroSubSecondDigits:suppressZeroSubSecondDigits
+    timeSeparator:tSep timeOnly:timeOnly 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
+        numDigits: nr of post-second fractional part (i.e. 3 for millis, 6 for micros, 0 for none, #variable for as-required);
+        suppressZeroSubSecondDigits: to suppress zeros (i.e. the old behavior).
+     if timeOnly is true, only the time is printed."
+
+    |aTimestamp timeInfo picos picosString |
+
+    aTimestamp := aTimeOrTimestamp asTimestamp.
+
+    asLocal ifTrue:[
+        "/ force local
+        timeInfo := aTimestamp asLocalTimestamp timeInfo.
+    ] ifFalse:[
+        asUTC ifTrue:[
+            "/ force utc
+            timeInfo := aTimestamp asUtcTimestamp timeInfo.
+        ] ifFalse:[
+            "/ in the timestamps own format
+            timeInfo := aTimestamp timeInfo.
+        ]
+    ].
+
+    timeOnly ifFalse:[
+        timeInfo year printOn:aStream leftPaddedTo:4 with:$0.
+        compact ifFalse:[ aStream nextPut: $- ].
+        timeInfo month printOn:aStream leftPaddedTo:2 with:$0.
+        compact ifFalse:[ aStream nextPut: $- ].
+        timeInfo day printOn:aStream leftPaddedTo:2 with:$0.
+        aStream nextPut:tSep.
+    ].
+    timeInfo hours printOn:aStream leftPaddedTo:2 with:$0.
+    compact ifFalse:[ aStream nextPut: $:].
+    timeInfo minutes printOn:aStream leftPaddedTo:2 with:$0.
+
+    "always print the seconds, even if 0. 
+     According to http://www.w3.org/TR/xmlschema11-2/#dateTime  this is mandatory"
+
+    compact ifFalse:[ aStream nextPut: $:].
+    timeInfo seconds printOn:aStream leftPaddedTo:2 with:$0.
+
+    (numDigits == 3 and:[suppressZeroSubSecondDigits not]) ifTrue:[
+        "/ special case, because it is so common
+        aStream nextPut: $..
+        aTimestamp milliseconds printOn:aStream leftPaddedTo:3 with:$0.
+    ] ifFalse:[
+        numDigits ~~ 0 ifTrue:[
+            picos := aTimestamp picoseconds.    
+            (suppressZeroSubSecondDigits and:[picos = 0]) ifFalse:[
+                "/ not suppressed    
+                picosString := picos printStringLeftPaddedTo:12 with:$0.
+                numDigits == #variable ifTrue:[
+                    picosString := picosString withoutTrailing:$0.
+                ] ifFalse:[    
+                    numDigits > 12 ifTrue:[
+                        picosString := picosString paddedTo:numDigits with:$0
+                    ] ifFalse:[
+                        picosString := picosString copyTo:numDigits.
+                    ].                
+                ].    
+                aStream nextPut: $..
+                aStream nextPutAll:picosString.
+            ]    
+        ].    
+    ].
+    
+    asUTC ifTrue:[
+        aStream nextPut: $Z
+    ] ifFalse:[
+        asLocal ifFalse:[
+            self printTimeZone:aTimestamp utcOffset on:aStream.
+        ].
+    ].
+
+    "
+     Transcript cr. self 
+        print:(Timestamp nowWithMicroseconds) 
+        compact:false asLocal:false asUTC:true 
+        subSecondDigits:3
+        suppressZeroSubSecondDigits:false
+        timeSeparator:$T timeOnly:false on:Transcript
+        
+     Transcript cr. self 
+        print:(Timestamp nowWithMicroseconds) 
+        compact:false asLocal:false asUTC:true 
+        subSecondDigits:6
+        suppressZeroSubSecondDigits:false
+        timeSeparator:$T timeOnly:false on:Transcript
+
+     Transcript cr. self 
+        print:(Timestamp nowWithMicroseconds) 
+        compact:false asLocal:false asUTC:true 
+        subSecondDigits:#variable
+        suppressZeroSubSecondDigits:false
+        timeSeparator:$T timeOnly:false on:Transcript
+
+     Transcript cr. self 
+        print:(Timestamp now) 
+        compact:false asLocal:false asUTC:true 
+        subSecondDigits:#variable
+        suppressZeroSubSecondDigits:false
+        timeSeparator:$T timeOnly:false on:Transcript
+
+     Transcript cr. self 
+        print:(Timestamp now) 
+        compact:false asLocal:false asUTC:true 
+        subSecondDigits:1
+        suppressZeroSubSecondDigits:false
+        timeSeparator:$T timeOnly:false on:Transcript
+
+     Transcript cr. self 
+        print:(Timestamp now) 
+        compact:false asLocal:false asUTC:true 
+        subSecondDigits:0
+        suppressZeroSubSecondDigits:false
+        timeSeparator:$T timeOnly:false on:Transcript
+    "
+
+    "Created: / 15-06-2005 / 17:56:51 / masca"
+    "Modified: / 26-05-2018 / 13:43:00 / Claus Gittinger"
+!
+
 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"
+        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
+        print:aTimestamp
+        compact:compact asLocal:asLocal asUTC:asUTC
+        withMilliseconds:withMillis
+        timeSeparator:$T timeOnly:false
+        on:aStream
 
     "
      self print:(Timestamp now) on:Transcript
      self printAsLocalTime:(Timestamp now) on:Transcript
      self printAsLocalTime:(Timestamp now asTZTimestamp:-7200) on:Transcript
     "
+
+    "Modified: / 26-05-2018 / 13:43:39 / Claus Gittinger"
 !
 
 print:aTimestamp compact:compact asLocal:asLocal asUTC:asUTC withMilliseconds:withMillis timeSeparator:tSep on:aStream
@@ -3549,50 +4442,11 @@
                     otherwise it is a timestamp from another timezone (TZTimestamp), then print in its timezone
         withMilliseconds: if false, no milliseconds are generated"
 
-    |timeInfo millis |
-
-    asLocal ifTrue:[
-        "/ force local
-        timeInfo := aTimestamp asLocalTimestamp timeInfo.
-    ] ifFalse:[
-        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.
-    compact ifFalse:[ aStream nextPut: $- ].
-    timeInfo month printOn:aStream leftPaddedTo:2 with:$0.
-    compact ifFalse:[ aStream nextPut: $- ].
-    timeInfo day printOn:aStream leftPaddedTo:2 with:$0.
-    aStream nextPut:tSep.
-    timeInfo hours printOn:aStream leftPaddedTo:2 with:$0.
-    compact ifFalse:[ aStream nextPut: $:].
-    timeInfo minutes printOn:aStream leftPaddedTo:2 with:$0.
-
-    "always print the seconds, even if 0. 
-     According to http://www.w3.org/TR/xmlschema11-2/#dateTime  this is mandatory"
-
-    compact ifFalse:[ aStream nextPut: $:].
-    timeInfo seconds printOn:aStream leftPaddedTo:2 with:$0.
-
-    millis := withMillis ifTrue:[timeInfo milliseconds] ifFalse:[0].
-    millis ~= 0 ifTrue:[
-        aStream nextPut: $..
-        millis printOn:aStream leftPaddedTo:3 with:$0.
-    ].
-
-    asUTC ifTrue:[
-        aStream nextPut: $Z
-    ] ifFalse:[
-        asLocal ifFalse:[
-            self printTimeZone:aTimestamp utcOffset on:aStream.
-        ].
-    ].
+    self 
+        print:aTimestamp 
+        compact:compact asLocal:asLocal asUTC:asUTC 
+        withMilliseconds:withMillis timeSeparator:tSep timeOnly:false
+        on:aStream
 
     "
      self print:(Timestamp now) on:Transcript
@@ -3601,26 +4455,72 @@
     "
 
     "Created: / 15-06-2005 / 17:56:51 / masca"
+!
+
+print:aTimeOrTimestamp compact:compact asLocal:asLocal asUTC:asUTC 
+    withMilliseconds:withMillis timeSeparator:tSep timeOnly:timeOnly 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.
+     if timeOnly is true, only the time is printed.
+     Warning: this has a feature (a bug) of implicitly suppressing fractional seconds, if the millis are zero.
+              this is strange, but for backward compatibility, left as is
+              (in case some printout depends on it)"
+
+    |nDigits|
+
+    nDigits := withMillis ifTrue:[3] ifFalse:[0].
+    self 
+        print:aTimeOrTimestamp 
+        compact:compact asLocal:asLocal asUTC:asUTC 
+        subSecondDigits:nDigits
+        suppressZeroSubSecondDigits:true
+        timeSeparator:tSep timeOnly:timeOnly on:aStream
+
+
+    "
+     self print:(Timestamp now) on:Transcript
+     self print:(Time now) on:Transcript
+     self printAsLocalTime:(Timestamp now) on:Transcript
+     self printAsLocalTime:(Timestamp now asTZTimestamp:-7200) on:Transcript
+    "
+
+    "Created: / 15-06-2005 / 17:56:51 / masca"
 ! !
 
 !Timestamp::TimestampISO8601Builder class methodsFor:'public parsing'!
 
-read: stringOrStream withClass:timestampClass
+read:stringOrStream withClass:timestampClass
     ^ self new read:stringOrStream withClass:timestampClass
 
     "Created: / 15-06-2005 / 17:52:03 / masca"
 !
 
-read: stringOrStream withClass:timestampClass yearAlreadyReadAs:yearArg
+read:stringOrStream withClass:timestampClass yearAlreadyReadAs:yearArg
     "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"
 ! !
 
+!Timestamp::TimestampISO8601Builder methodsFor:'accessing'!
+
+stream:something
+    stream := something.
+! !
+
 !Timestamp::TimestampISO8601Builder methodsFor:'private-reading'!
 
 nextDigit
@@ -3650,20 +4550,31 @@
     "Modified: / 15-06-2005 / 17:22:52 / masca"
 !
 
-nextDigits: anInteger
-
-    | char number |
+nextDigits:anInteger
+    ^ self nextDigitsAtLeast:anInteger atMost:anInteger
+
+!
+
+nextDigitsAtLeast:minCount atMost:maxCount
+    |count char number|
+
     number := 0.
-    anInteger timesRepeat: [
-	char := stream peekOrNil.
-	char ifNil: [self malformed: 'Stream does not contain all ' , anInteger printString , ' digits'].
-	char isDigit
-	    ifTrue: [
-		stream next.
-		number := number * 10 + char codePoint - $0 codePoint]
-	    ifFalse: [self malformed: 'Requested ' , anInteger printString , ' digits not found']
-    ].
-    ^ number
+    count := 0.
+    [
+        char := stream peekOrNil.
+        (char notNil and:[char isDigit]) ifFalse:[
+            count < minCount ifTrue:[
+                self malformed:('Stream does not contain at least %1 digits' bindWith:minCount)
+            ].
+            ^ number
+        ].
+        stream next.
+        number := (number * 10) + char digitValue.
+        count := count + 1.
+        count == maxCount ifTrue:[
+            ^ number
+        ].
+    ] loop.
 
     "Created: / 14-06-2005 / 11:57:22 / masca"
     "Modified: / 15-06-2005 / 15:54:29 / masca"
@@ -3722,7 +4633,7 @@
 
     peek := stream peekOrNil.
     peek ifNil: [
-        "End of stream, only year has been read."
+        "End of stream, only date has been read."
         ^ self timestampWithClass:timestampClass].
 
     (peek asUppercase == $T or: [peek == Character space])
@@ -3746,48 +4657,22 @@
     "Read an arbitrary number of digits representing a fraction."
 
     ^ Fraction readDecimalFractionFrom:stream onError:[self malformed: 'Missing digits after fraction separator'].
-"/
-"/    | anyDigit digit factor fraction |
-"/
-"/    factor := (1 / 10).
-"/    fraction := 0.
-"/    anyDigit := false.
-"/
-"/    [
-"/        digit := self nextDigit.
-"/        digit >= 0
-"/    ] whileTrue: [
-"/        anyDigit := true.
-"/        fraction := digit * factor + fraction.
-"/        factor := (factor / 10)
-"/    ].
-"/
-"/    anyDigit ifFalse: [self malformed: 'Missing digits after fraction separator'].
-"/    ^ fraction
-"/
+
+    "
+     (Fraction readDecimalFractionFrom:'12345' readStream onError:nil)
+    "
 !
 
 readMilliseconds
-    "Read an arbitrary number of digits representing milliseconds. As the timestamp can
-    hold only integer amounts of milliseconds, don't mind the rest of the digits."
-
-    millisecond := (self readFraction * 1000) asInteger
-"/    | digit factor |
-"/
-"/    factor := 100.
-"/
-"/    [
-"/        digit := self nextDigit.
-"/        digit >= 0
-"/    ] whileTrue: [
-"/        factor > 0 ifTrue: [
-"/            "Factor still > 0, did not read all three digits of mantissa."
-"/            millisecond := digit * factor + millisecond.
-"/            factor := (factor / 10) integerPart
-"/        ]
-"/    ].
-"/
-"/    factor = 100 ifTrue: [self malformed: 'No digits after millisecond separator']
+    "Read an arbitrary number of digits representing the fractional part
+     (used to be milliseconds, but now we can represent anything down to pico seconds"
+
+    |fraction ms|
+
+    fraction := self readFraction.  "/ 0 .. 0.99999...
+    ms := (fraction * 1000).        "/ 0 .. 999.999999
+    millisecond := (ms // 1).       "/ 0 .. 999
+    picos := (ms \\ 1) * (1000 * 1000 * 1000).
 
     "Created: / 15-06-2005 / 15:25:45 / masca"
 !
@@ -3796,39 +4681,42 @@
     "Read month number, optionally followed by day, or absolute day number (three digit)."
 
     | dayDigit1 dayDigit2 |
-    month := self nextDigits: 2.
-
-    stream peekOrNil = $-
-	ifTrue: [
-	    "Got dash. Day number must follow."
-	    stream next.
-	    day := self nextDigits: 2.
-	    (self isAllowedDay: day) ifFalse: [self malformed: 'Bad day: ' , day printString].
-	    ^self].
+
+    month := self nextDigitsAtLeast:1 atMost:2.
+
+    stream peekOrNil == $- ifTrue: [
+        "Got dash. Day number must follow."
+        stream next.
+        day := self nextDigitsAtLeast:1 atMost: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]]
+    dayDigit2 < 0 ifTrue: [
+        "Read only three digits, this is absolute day number in a year."
+        self dateFromDayNumber: month * 10 + dayDigit1
+    ] ifFalse: [
+        "Read four digits. So there's month and day."
+        (month between: 1 and: 12) ifFalse: [self malformed: 'Bad month: ' , month printString].
+        day := dayDigit1 * 10 + dayDigit2.
+        (self isAllowedDay: day) ifFalse: [self malformed: 'Bad day: ' , day printString]
+    ].
 
     "Created: / 15-06-2005 / 11:12:02 / masca"
     "Modified: / 16-06-2005 / 11:47:34 / masca"
 !
 
 readTime
-    "Date read, don't mind it. Read only the time value."
+    "Date already read, don't mind it. 
+     Read only the time value."
 
     | peek f |
 
@@ -3927,8 +4815,8 @@
 
 readTimezone
     "Read time zone information. There are three possibilities of what can occur.
-    If there is nothing more to read, the offset is unknown - this is treated as
-    Zulu time as this may not be true."
+     If there is nothing more to read, the offset is unknown - this is treated as
+     Zulu time as this may not be true."
 
     | peek tzOffset |
 
@@ -3937,7 +4825,7 @@
     peek := peek asUppercase.
 
     "If the time is in Zulu, don't modify the timestamp. This makes the machine
-    run in Zulu time zone, maybe some corrections would be nice."
+     run in Zulu time zone, maybe some corrections would be nice."
     peek == $Z ifTrue: [
         "Time read, skip Zulu signature and exit."
         isUtcTime := true.
@@ -3966,7 +4854,8 @@
 
 readTimezoneOffset
     "Read time zone offset as a number minutes. Generally, there should be hours only
-    but as the format introduces minutes in offsets, we must accept them."
+     but as the format introduces minutes in offsets, we must accept them.
+     (actually: there are countries with half-hour offsets!!)"
 
     | hours digit |
 
@@ -3975,12 +4864,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."
@@ -3996,21 +4885,21 @@
 !
 
 readWeekNumber
+    "Read week number. It is always two digits long."
 
     | week dayInWeek digit |
 
-    "Read week number. It is always two digits long."
     week := self nextDigits: 2.
 
     stream peekOrNil = $-
-	ifTrue: [
-	    "Got dash, day number must follow."
-	    stream next.
-	    digit := self nextDigit.
-	    digit < 0 ifTrue: [self malformed: 'Bad weekday number'].
-	    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.