Timestamp.st
changeset 17071 3d4803aa1b4f
parent 17067 b32e90d1cc4d
child 17079 76e263370574
--- a/Timestamp.st	Tue Nov 18 17:16:00 2014 +0100
+++ b/Timestamp.st	Tue Nov 18 17:21:33 2014 +0100
@@ -425,7 +425,6 @@
     "Modified: / 13.7.1999 / 12:30:26 / stefan"
 ! !
 
-
 !Timestamp class methodsFor:'private'!
 
 basicReadFrom:aStream
@@ -438,9 +437,9 @@
      it is assumed to be a year and the rest is read in iso8601 format.
 
      KLUDGE:
-	us and non-us format have different ordering of day and month;
-	The format read here is (non-us) dd-mm-yyyy hh:mm:ss.iii
-	or (us-format, for Travis) mm/dd/yyyy hh:mm:ss.iii.
+        us and non-us format have different ordering of day and month;
+        The format read here is (non-us) dd-mm-yyyy hh:mm:ss.iii
+        or (us-format, for Travis) mm/dd/yyyy hh:mm:ss.iii.
      On error, raise an exception"
 
     |pos firstNumber secondNumber day month year hour min sec millis usFormat possibeMonthName ch utcOffsetOrNil|
@@ -448,9 +447,9 @@
     pos := aStream position.
     firstNumber := Integer readFrom:aStream onError:[TimeConversionError raiseErrorString:' - integer expected'].
     firstNumber > 31 ifTrue:[
-	"/ assume iso8601 format;
-	aStream position:pos.
-	^ self readIso8601FormatFrom:aStream.
+        "/ assume iso8601 format;
+        aStream position:pos.
+        ^ self readIso8601FormatFrom:aStream.
     ].
     aStream skipSeparators.
 
@@ -459,20 +458,20 @@
 
     [(ch := aStream peekOrNil) notNil and:[ch isLetterOrDigit]] whileFalse:[aStream next].
     ((ch := aStream peekOrNil) notNil and:[ch isDigit]) ifTrue:[
-	secondNumber := Integer readFrom:aStream onError:-1.
-
-	usFormat ifTrue:[
-	    month := firstNumber.
-	    day := secondNumber.
-	] ifFalse:[
-	    month := secondNumber.
-	    day := firstNumber.
-	].
+        secondNumber := Integer readFrom:aStream onError:-1.
+
+        usFormat ifTrue:[
+            month := firstNumber.
+            day := secondNumber.
+        ] ifFalse:[
+            month := secondNumber.
+            day := firstNumber.
+        ].
 
     ] ifFalse:[
-	possibeMonthName := aStream throughAnyForWhich:[:ch | ch isLetter].
-	month := Date indexOfMonth:possibeMonthName asLowercase.
-	day := firstNumber.
+        possibeMonthName := aStream throughAnyForWhich:[:ch | ch isLetter].
+        month := Date indexOfMonth:possibeMonthName asLowercase.
+        day := firstNumber.
     ].
 
     (day between:1 and:31) ifFalse:[ TimeConversionError raiseErrorString:' - bad day' ].
@@ -482,46 +481,48 @@
     year := Integer readFrom:aStream onError:[ TimeConversionError raiseErrorString:' - bad year' ].
 
     aStream atEnd ifTrue:[
-	hour := min := sec := millis := 0.
+        hour := min := sec := millis := 0.
     ] ifFalse:[
-	[(ch := aStream peekOrNil) notNil and:[ch isDigit not]] whileTrue:[aStream next].
-	hour := Integer readFrom:aStream onError:-1.
-	(hour between:0 and:24) ifFalse:[ TimeConversionError raiseErrorString:' - bad hour' ].
-
-	[(ch := aStream peekOrNil) notNil and:[ch isDigit not]] whileTrue:[aStream next].
-	min := Integer readFrom:aStream onError:-1.
-	(min between:0 and:59) ifFalse:[ TimeConversionError raiseErrorString:' - bad minute' ].
-
-	aStream atEnd ifTrue:[
-	    sec := millis := 0.
-	] ifFalse:[
-	    [(ch := aStream peekOrNil) notNil and:[ch isDigit not]] whileTrue:[aStream next].
-	    sec := Integer readFrom:aStream onError:-1.
-	    (sec between:0 and:59) ifFalse:[ TimeConversionError raiseErrorString:' - bad second' ].
-
-	    aStream peek == $. ifTrue:[
-		aStream next.
-		millis := Integer readFrom:aStream onError:0.
-		millis >= 1000 ifTrue:[ TimeConversionError raiseErrorString:' - bad millisecond' ].
-	    ] ifFalse:[
-		millis := 0.
-	    ].
-	    utcOffsetOrNil := self utcOffsetFrom:aStream
-	].
+        [(ch := aStream peekOrNil) notNil and:[ch isDigit not]] whileTrue:[aStream next].
+        hour := Integer readFrom:aStream onError:-1.
+        (hour between:0 and:24) ifFalse:[ TimeConversionError raiseErrorString:' - bad hour' ].
+
+        [(ch := aStream peekOrNil) notNil and:[ch isDigit not]] whileTrue:[aStream next].
+        min := Integer readFrom:aStream onError:-1.
+        (min between:0 and:59) ifFalse:[ TimeConversionError raiseErrorString:' - bad minute' ].
+
+        aStream atEnd ifTrue:[
+            sec := millis := 0.
+        ] ifFalse:[
+            [(ch := aStream peekOrNil) notNil and:[ch isDigit not]] whileTrue:[aStream next].
+            sec := Integer readFrom:aStream onError:-1.
+            (sec between:0 and:59) ifFalse:[ TimeConversionError raiseErrorString:' - bad second' ].
+
+            aStream peek == $. ifTrue:[
+                aStream next.
+                millis := Integer readFrom:aStream onError:0.
+                millis >= 1000 ifTrue:[ TimeConversionError raiseErrorString:' - bad millisecond' ].
+            ] ifFalse:[
+                millis := 0.
+            ].
+            aStream atEnd ifFalse:[
+                utcOffsetOrNil := self utcOffsetFrom:aStream
+            ].
+        ].
     ].
 
     "special check - only 24:00:00 is allowed;
      every time after that must wrap"
     hour == 24 ifTrue:[
-	(min ~~ 0 or:[sec ~~ 0 or:[millis ~~ 0]]) ifTrue:[ TimeConversionError raiseErrorString:' - bad hour' ].
+        (min ~~ 0 or:[sec ~~ 0 or:[millis ~~ 0]]) ifTrue:[ TimeConversionError raiseErrorString:' - bad hour' ].
     ].
     utcOffsetOrNil notNil ifTrue:[
-	utcOffsetOrNil := utcOffsetOrNil negated.
-	utcOffsetOrNil = 0 ifTrue:[
-	    "/ utc timestamp
-	    ^ UtcTimestamp year:year month:month day:day hour:hour minute:min second:sec millisecond:millis
-	].
-	^ ((TZTimestamp year:year month:month day:day hour:hour minute:min second:sec millisecond:millis) utcOffset:utcOffsetOrNil) - utcOffsetOrNil
+        utcOffsetOrNil := utcOffsetOrNil negated.
+        utcOffsetOrNil = 0 ifTrue:[
+            "/ utc timestamp
+            ^ UtcTimestamp year:year month:month day:day hour:hour minute:min second:sec millisecond:millis
+        ].
+        ^ ((TZTimestamp year:year month:month day:day hour:hour minute:min second:sec millisecond:millis) utcOffset:utcOffsetOrNil) - utcOffsetOrNil
     ].
     "/ a local timestamp
     ^ self year:year month:month day:day hour:hour minute:min second:sec millisecond:millis.
@@ -1541,40 +1542,41 @@
      UtcOffset is what you have to ADD to correct the printed time to GMT.
      I.e. for Germany, you'll get -3600 (+01h), for NewYork, you'll get +18000 (-05h)"
 
-    |table i offset stream tzName sign|
+    |ch table i offset stream tzName sign|
 
     table := self timezoneInfo.
 
     stream := aStringOrStream readStream.
     stream skipSeparators.
 
-    stream peek isLetter ifTrue:[
-	tzName := stream upToElementForWhich:[:ch | ch isLetter not].
-
-	i := table indexOf:tzName.
-	i == 0 ifTrue:[
-	    ^ nil
-	].
-	offset := (table at:i+1) * 60 * 60
+    ch := stream peekOrNil isNil ifTrue:[^ 0].
+    ch isLetter ifTrue:[
+        tzName := stream upToElementForWhich:[:ch | ch isLetter not].
+
+        i := table indexOf:tzName.
+        i == 0 ifTrue:[
+            ^ nil
+        ].
+        offset := (table at:i+1) * 60 * 60
     ] ifFalse:[
-	sign := 1.
-	stream peek == $- ifTrue:[
-	    sign := -1.
-	    stream next.
-	] ifFalse:[
-	    stream peek == $+ ifTrue:[
-		sign := 1.
-		stream next.
-	    ] ifFalse:[
-		stream skipSeparators
-	    ]
-	].
-	offset := ((stream next:2) asNumber * 60 * 60).
-	stream peekOrNil notNil ifTrue:[
-	    stream peek == $: ifTrue:[ stream next ].
-	    offset := offset + ((stream next:2) asNumber * 60).
-	].
-	offset := offset * sign
+        sign := 1.
+        ch == $- ifTrue:[
+            sign := -1.
+            stream next.
+        ] ifFalse:[
+            ch == $+ ifTrue:[
+                sign := 1.
+                stream next.
+            ] ifFalse:[
+                stream skipSeparators
+            ]
+        ].
+        offset := ((stream next:2) asNumber * 60 * 60).
+        stream peekOrNil notNil ifTrue:[
+            stream peek == $: ifTrue:[ stream next ].
+            offset := offset + ((stream next:2) asNumber * 60).
+        ].
+        offset := offset * sign
     ].
 
     "/ return what would be an utcOffset (not what is at the end of an iso string)
@@ -1604,7 +1606,6 @@
     "
 ! !
 
-
 !Timestamp methodsFor:'accessing'!
 
 day
@@ -2936,8 +2937,6 @@
     "
 ! !
 
-
-
 !Timestamp methodsFor:'testing'!
 
 isLocalTimestamp
@@ -3915,11 +3914,11 @@
 !Timestamp class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Timestamp.st,v 1.203 2014-11-18 14:45:10 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Timestamp.st,v 1.204 2014-11-18 16:21:33 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Timestamp.st,v 1.203 2014-11-18 14:45:10 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Timestamp.st,v 1.204 2014-11-18 16:21:33 cg Exp $'
 ! !