*** empty log message ***
authorclaus
Wed, 08 Feb 1995 04:11:17 +0100
changeset 241 6f30be88e314
parent 240 f5ff68fffb92
child 242 0190f298e56c
*** empty log message ***
AbsTime.st
AbsoluteTime.st
BContext.st
BlockContext.st
Date.st
LinkList.st
LinkedList.st
Make.proto
MiniDebug.st
MiniDebugger.st
ProcSched.st
ProcessorScheduler.st
Time.st
Timestamp.st
Unix.st
--- a/AbsTime.st	Wed Feb 08 04:10:51 1995 +0100
+++ b/AbsTime.st	Wed Feb 08 04:11:17 1995 +0100
@@ -10,18 +10,20 @@
  hereby transferred.
 "
 
-Magnitude subclass:#AbsoluteTime
-       instanceVariableNames:'secondsLow secondsHi'
-       classVariableNames:''
-       poolDictionaries:''
-       category:'Magnitude-General'
+'From Smalltalk/X, Version:2.10.4 on 8-feb-1995 at 12:46:45 pm'!
+
+AbstractTime subclass:#AbsoluteTime
+	 instanceVariableNames:'secondsLow secondsHi'
+	 classVariableNames:''
+	 poolDictionaries:''
+	 category:'Magnitude-General'
 !
 
 AbsoluteTime comment:'
 COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libbasic/Attic/AbsTime.st,v 1.7 1994-11-28 20:32:07 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Attic/AbsTime.st,v 1.8 1995-02-08 03:10:47 claus Exp $
 '!
 
 !AbsoluteTime class methodsFor:'documentation'!
@@ -42,7 +44,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libbasic/Attic/AbsTime.st,v 1.7 1994-11-28 20:32:07 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Attic/AbsTime.st,v 1.8 1995-02-08 03:10:47 claus Exp $
 "
 !
 
@@ -51,9 +53,10 @@
     This class represents time values in seconds from 1st. Jan 1970, as
     used in the Unix operating system. Its implementation is not the same
     as in ST-80 (which represents Time as seconds from 1. Jan 1901.
-    Actually, the implementation does not even know which time/date the
-    OperatingSystem bases its time upon - it is simply keeping the value(s)
-    as return from the OS when asked for the time.
+
+    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 return 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 time-stamps on files (such as last-access-
@@ -64,76 +67,74 @@
     we keep low and hi 16bits of the time separately (it could have been 
     implemented using LargeIntegers though).
 
-    This class is typically abstract (it does not have to be, though).
+    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 AbsoluteTime can.
+
     See Time for more details.
 "
 ! !
 
 !AbsoluteTime class methodsFor:'instance creation'!
 
-secondClock
-    "return seconds of now - for GNU-ST compatibility"
+day:d month:m year:y hour:h minutes:min seconds:s
+    "return an instance of the receiver"
 
-    ^ OperatingSystem getTime
-!
+    ^ self fromOSTime:(OperatingSystem 
+                        computeTimePartsFromYear:y month:m day:d 
+                                            hour:h minute:min seconds:s)
 
-millisecondClockValue
-    "return the millisecond clock - since this one overruns
-     regularly, use only for short timing deltas."
+    "
+     AbsoluteTime day:2 month:1 year:1991 hour:12 minutes:30 seconds:0 
+     AbsoluteTime day:8 month:1 year:1995 hour:0 minutes:43 seconds:48 
+    "
+! !
 
-    ^ OperatingSystem getMillisecondTime.
-!
+!AbsoluteTime methodsFor:'private'!
 
-fromUnixTimeLow:low and:hi
-    "return an instance of Time, given the unix time.
-     Internal interface - not for public use."
-
-    ^ self basicNew setSecondsLow:low and:hi
+secondsLow
+    ^ secondsLow
 !
 
-dateAndTimeNow
-    "return an array filled with date and time"
-
-    ^ Array with:(Date today) with:(Time now)
-! !
-
-!AbsoluteTime class methodsFor:'timing evaluations'!
+setSecondsLow:secsLow and:secsHi
+    secondsHi := secsHi.
+    secondsLow := secsLow
+!
 
-secondsToRun:aBlock
-    "evaluate the argument, aBlock; return the number of seconds it took"
-
-    |startTime endTime|
-
-    startTime := self now.
-    aBlock value.
-    endTime := self now.
-    ^ endTime - startTime
+fromOSTimeLow:secsLow and:secsHi
+    secondsHi := secsHi.
+    secondsLow := secsLow
 !
 
-millisecondsToRun:aBlock
-    "evaluate the argument, aBlock; return the number of milliseconds it took"
-
-    |startTime endTime|
+secondsHi
+    ^ secondsHi
+!
 
-    startTime := self millisecondClockValue.
-    aBlock value.
-    endTime := self millisecondClockValue.
-    ^ endTime - startTime
+setSeconds:secs
+    secondsHi := secs // 16r10000.
+    secondsLow := secs \\ 16r10000
+!
+
+getSeconds
+    ^ (secondsHi * 16r10000) + secondsLow
+!
+
+fromOSTime:secs
+    secondsHi := secs // 16r10000.
+    secondsLow := secs \\ 16r10000
 ! !
 
 !AbsoluteTime methodsFor:'accessing'!
 
 hourInDay
-    "return the hour-part"
+    "return the hours (0..23)"
 
-    |hr|
+    ^ self hours
 
-    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
-	:hours :minutes :secs |
+    "
+     AbsoluteTime now hours 
+    "
 
-	hr := hours
-    ].
-    ^ hr
 !
 
 minuteInDay
@@ -142,11 +143,16 @@
     |m|
 
     OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
-	:hours :minutes :secs |
+        :hours :minutes :secs |
 
-	m := minutes
+        m := minutes
     ].
     ^ m
+
+    "
+     AbsoluteTime now minuteInDay 
+    "
+
 !
 
 secondInDay
@@ -155,24 +161,32 @@
     |s|
 
     OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
-	:hours :minutes :secs |
+        :hours :minutes :secs |
 
-	s := secs
+        s := secs
     ].
     ^ s
+
+    "
+     AbsoluteTime now secondInDay 
+    "
+
 !
 
 day
     "return the day-in-month of the receiver (1..31).
      Obsolete; use instances of Date for this."
 
+    |d|
+
     OperatingSystem computeDatePartsOf:secondsLow and:secondsHi
-				   for:[:year :month :day |
-	^ day
-    ]
+                                   for:[:year :month :day |
+        d := day
+    ].
+    ^ d
 
     "
-     Time now day
+     AbsoluteTime now day 
     "
 !
 
@@ -180,13 +194,16 @@
     "return the month of the receiver (1..12).
      Obsolete; use instances of Date for this."
 
+    |m|
+
     OperatingSystem computeDatePartsOf:secondsLow and:secondsHi
-				   for:[:year :month :day |
-	^ month
-    ]
+                                   for:[:year :month :day |
+        m := month
+    ].
+    ^ m
 
     "
-     Time now month
+     AbsoluteTime now month
     "
 !
 
@@ -194,14 +211,71 @@
     "return the year of the receiver i.e. 1992.
      Obsolete; use instances of Date for this."
 
+    |y|
+
     OperatingSystem computeDatePartsOf:secondsLow and:secondsHi
-				   for:[:year :month :day |
-	^ year
-    ]
+                                   for:[:year :month :day |
+        y := year
+    ].
+    ^ y
+
+    "
+     AbsoluteTime now year
+    "
+!
+
+hours
+    "return the hours (0..23)"
+
+    |hr|
+
+    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
+        :hours :minutes :secs |
+
+        hr := hours
+    ].
+    ^ hr
 
     "
-     Time now year
+     AbsoluteTime now hours 
+    "
+
+!
+
+minutes
+    "return the minutes (0..59)"
+
+    |m|
+
+    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
+        :hours :minutes :secs |
+
+        m := minutes
+    ].
+    ^ m
+
+    "
+     AbsoluteTime now minutes 
     "
+
+!
+
+seconds
+    "return the seconds (0..59)"
+
+    |s|
+
+    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
+        :hours :minutes :secs |
+
+        s := secs
+    ].
+    ^ s
+
+    "
+     AbsoluteTime now seconds 
+    "
+
 ! !
 
 !AbsoluteTime methodsFor:'comparing'!
@@ -229,6 +303,51 @@
     ^ (secondsLow bitShift:16) bitOr:secondsLow
 ! !
 
+!AbsoluteTime methodsFor:'converting'!
+
+asSeconds
+    "return the number of seconds elapsed since whatever time the
+     OperatingSystem bases its time upon. Since this is totally
+     OS-dependent, do not interpret the value returned by this method.
+     You can use it to add/subtract seconds or get time deltas, though."
+
+    ^ (secondsHi * 16r10000) + secondsLow
+
+    "
+     AbsoluteTime now asSeconds
+     AbsoluteTime fromSeconds:(AbsoluteTime now asSeconds + 3600) 
+     Time hour:23 minutes:33 seconds:0         
+     Time fromSeconds:((Time hour:23 minutes:33 seconds:0) asSeconds + 3600) 
+    "
+!
+
+asDate
+    "return a Date object from the receiver"
+
+    ^ Date fromOSTime:(Array with:secondsLow with:secondsHi) 
+
+    "
+     AbsoluteTime now  
+     AbsoluteTime now asDate
+     (AbsoluteTime now addTime:3600) asDate 
+     (AbsoluteTime now addTime:3600) asTime 
+     AbsoluteTime fromSeconds:(AbsoluteTime now asSeconds + 3600) 
+     (AbsoluteTime fromSeconds:(AbsoluteTime now asSeconds + 3600)) asDate  
+    "
+
+!
+
+asTime
+    ^ Time fromOSTime:(Array with:secondsLow with:secondsHi)
+
+    "
+     AbsoluteTime now  
+     AbsoluteTime now asTime
+     (AbsoluteTime now addTime:3600) asTime 
+    "
+
+! !
+
 !AbsoluteTime methodsFor:'arithmetic'!
 
 - aTime
@@ -238,73 +357,61 @@
 !
 
 addTime:timeAmount
-    "return a new Time/Date timeAmount seconds from myself"
+    "return a new instance of myself, timeAmount seconds afterwards"
 
     ^ self class new setSeconds:(self getSeconds + timeAmount)
 !
 
 subtractTime:timeAmount
-    "return a new Time/Date timeAmount seconds before myself"
+    "return a new instance opf myself, timeAmount seconds before myself"
 
     ^ self class new setSeconds:(self getSeconds - timeAmount)
 ! !
 
 !AbsoluteTime methodsFor:'printing & storing'!
 
-storeString
-    |string|
+printOn:aStream
+    |h min s d m y|
 
-    string := '(' , self class name , ' new setSecondsLow:'.
-    string := string , secondsLow storeString.
-    string := string , ' and:' , secondsHi storeString.
-    string := string , ')'.
-    ^ string
-! !
-
-!AbsoluteTime methodsFor:'converting'!
-
-asSeconds
-    "return the number of seconds elapsed since whatever time the
-     OperatingSystem bases its time upon. Since this is totally
-     OS-dependent, do not use this method. (see Time>>asSeconds)"
-
-    ^ (secondsHi * 16r10000) + secondsLow
+    OperatingSystem computeDatePartsOf:secondsLow and:secondsHi for:[
+        :year :month :day | d := day. m := month. y := year.
+    ].
+    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
+        :hours :minutes :secs | h := hours. min := minutes. s := secs.
+    ].
+    d printOn:aStream.
+    aStream nextPut:$-.
+    m printOn:aStream.
+    aStream nextPut:$-.
+    y printOn:aStream.
+    aStream space.
+    h printOn:aStream leftPaddedTo:2 with:$0. 
+    aStream nextPut:$:.
+    min printOn:aStream leftPaddedTo:2 with:$0.
+    aStream nextPut:$:.
+    s printOn:aStream leftPaddedTo:2 with:$0.
 
     "
-     AbsoluteTime asSeconds
+     AbsoluteTime now 
+     AbsoluteTime fromSeconds:0 
+     Time now            
+     Date today         
     "
 !
 
-asDate
-    "return a Date object from the receiver"
+storeOn:aStream
+    aStream nextPut:$(; 
+            nextPutAll:self class name; 
+            nextPutAll:' new setSecondsLow:'.
+    secondsLow storeOn:aStream.
+    aStream nextPutAll:' and:'.
+    secondsHi storeOn:aStream.
+    aStream nextPut:$).
 
-    ^ Date fromOSTime:(Array with:secondsLow with:secondsHi) 
-!
+    "
+     AbsoluteTime now storeString '(AbsoluteTime new setSecondsLow:39757 and:12087)'
 
-asTime
-    ^ Time fromOSTime:(Array with:secondsLow with:secondsHi)
+     AbsoluteTime readFromString:(AbsoluteTime now storeString) 
+    "
 ! !
 
-!AbsoluteTime methodsFor:'private'!
-
-secondsLow
-    ^ secondsLow
-!
-
-secondsHi
-    ^ secondsHi
-!
-
-getSeconds
-    ^ (secondsHi * 16r10000) + secondsLow
-!
-
-setSeconds:secs
-    secondsHi := secs // 16r10000.
-    secondsLow := secs \\ 16r10000
-!
-
-setSecondsLow:secsLow and:secsHi
-    secondsHi := secsHi.
-    secondsLow := secsLow
-! !
--- a/AbsoluteTime.st	Wed Feb 08 04:10:51 1995 +0100
+++ b/AbsoluteTime.st	Wed Feb 08 04:11:17 1995 +0100
@@ -10,18 +10,20 @@
  hereby transferred.
 "
 
-Magnitude subclass:#AbsoluteTime
-       instanceVariableNames:'secondsLow secondsHi'
-       classVariableNames:''
-       poolDictionaries:''
-       category:'Magnitude-General'
+'From Smalltalk/X, Version:2.10.4 on 8-feb-1995 at 12:46:45 pm'!
+
+AbstractTime subclass:#AbsoluteTime
+	 instanceVariableNames:'secondsLow secondsHi'
+	 classVariableNames:''
+	 poolDictionaries:''
+	 category:'Magnitude-General'
 !
 
 AbsoluteTime comment:'
 COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libbasic/Attic/AbsoluteTime.st,v 1.7 1994-11-28 20:32:07 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Attic/AbsoluteTime.st,v 1.8 1995-02-08 03:10:47 claus Exp $
 '!
 
 !AbsoluteTime class methodsFor:'documentation'!
@@ -42,7 +44,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libbasic/Attic/AbsoluteTime.st,v 1.7 1994-11-28 20:32:07 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Attic/AbsoluteTime.st,v 1.8 1995-02-08 03:10:47 claus Exp $
 "
 !
 
@@ -51,9 +53,10 @@
     This class represents time values in seconds from 1st. Jan 1970, as
     used in the Unix operating system. Its implementation is not the same
     as in ST-80 (which represents Time as seconds from 1. Jan 1901.
-    Actually, the implementation does not even know which time/date the
-    OperatingSystem bases its time upon - it is simply keeping the value(s)
-    as return from the OS when asked for the time.
+
+    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 return 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 time-stamps on files (such as last-access-
@@ -64,76 +67,74 @@
     we keep low and hi 16bits of the time separately (it could have been 
     implemented using LargeIntegers though).
 
-    This class is typically abstract (it does not have to be, though).
+    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 AbsoluteTime can.
+
     See Time for more details.
 "
 ! !
 
 !AbsoluteTime class methodsFor:'instance creation'!
 
-secondClock
-    "return seconds of now - for GNU-ST compatibility"
+day:d month:m year:y hour:h minutes:min seconds:s
+    "return an instance of the receiver"
 
-    ^ OperatingSystem getTime
-!
+    ^ self fromOSTime:(OperatingSystem 
+                        computeTimePartsFromYear:y month:m day:d 
+                                            hour:h minute:min seconds:s)
 
-millisecondClockValue
-    "return the millisecond clock - since this one overruns
-     regularly, use only for short timing deltas."
+    "
+     AbsoluteTime day:2 month:1 year:1991 hour:12 minutes:30 seconds:0 
+     AbsoluteTime day:8 month:1 year:1995 hour:0 minutes:43 seconds:48 
+    "
+! !
 
-    ^ OperatingSystem getMillisecondTime.
-!
+!AbsoluteTime methodsFor:'private'!
 
-fromUnixTimeLow:low and:hi
-    "return an instance of Time, given the unix time.
-     Internal interface - not for public use."
-
-    ^ self basicNew setSecondsLow:low and:hi
+secondsLow
+    ^ secondsLow
 !
 
-dateAndTimeNow
-    "return an array filled with date and time"
-
-    ^ Array with:(Date today) with:(Time now)
-! !
-
-!AbsoluteTime class methodsFor:'timing evaluations'!
+setSecondsLow:secsLow and:secsHi
+    secondsHi := secsHi.
+    secondsLow := secsLow
+!
 
-secondsToRun:aBlock
-    "evaluate the argument, aBlock; return the number of seconds it took"
-
-    |startTime endTime|
-
-    startTime := self now.
-    aBlock value.
-    endTime := self now.
-    ^ endTime - startTime
+fromOSTimeLow:secsLow and:secsHi
+    secondsHi := secsHi.
+    secondsLow := secsLow
 !
 
-millisecondsToRun:aBlock
-    "evaluate the argument, aBlock; return the number of milliseconds it took"
-
-    |startTime endTime|
+secondsHi
+    ^ secondsHi
+!
 
-    startTime := self millisecondClockValue.
-    aBlock value.
-    endTime := self millisecondClockValue.
-    ^ endTime - startTime
+setSeconds:secs
+    secondsHi := secs // 16r10000.
+    secondsLow := secs \\ 16r10000
+!
+
+getSeconds
+    ^ (secondsHi * 16r10000) + secondsLow
+!
+
+fromOSTime:secs
+    secondsHi := secs // 16r10000.
+    secondsLow := secs \\ 16r10000
 ! !
 
 !AbsoluteTime methodsFor:'accessing'!
 
 hourInDay
-    "return the hour-part"
+    "return the hours (0..23)"
 
-    |hr|
+    ^ self hours
 
-    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
-	:hours :minutes :secs |
+    "
+     AbsoluteTime now hours 
+    "
 
-	hr := hours
-    ].
-    ^ hr
 !
 
 minuteInDay
@@ -142,11 +143,16 @@
     |m|
 
     OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
-	:hours :minutes :secs |
+        :hours :minutes :secs |
 
-	m := minutes
+        m := minutes
     ].
     ^ m
+
+    "
+     AbsoluteTime now minuteInDay 
+    "
+
 !
 
 secondInDay
@@ -155,24 +161,32 @@
     |s|
 
     OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
-	:hours :minutes :secs |
+        :hours :minutes :secs |
 
-	s := secs
+        s := secs
     ].
     ^ s
+
+    "
+     AbsoluteTime now secondInDay 
+    "
+
 !
 
 day
     "return the day-in-month of the receiver (1..31).
      Obsolete; use instances of Date for this."
 
+    |d|
+
     OperatingSystem computeDatePartsOf:secondsLow and:secondsHi
-				   for:[:year :month :day |
-	^ day
-    ]
+                                   for:[:year :month :day |
+        d := day
+    ].
+    ^ d
 
     "
-     Time now day
+     AbsoluteTime now day 
     "
 !
 
@@ -180,13 +194,16 @@
     "return the month of the receiver (1..12).
      Obsolete; use instances of Date for this."
 
+    |m|
+
     OperatingSystem computeDatePartsOf:secondsLow and:secondsHi
-				   for:[:year :month :day |
-	^ month
-    ]
+                                   for:[:year :month :day |
+        m := month
+    ].
+    ^ m
 
     "
-     Time now month
+     AbsoluteTime now month
     "
 !
 
@@ -194,14 +211,71 @@
     "return the year of the receiver i.e. 1992.
      Obsolete; use instances of Date for this."
 
+    |y|
+
     OperatingSystem computeDatePartsOf:secondsLow and:secondsHi
-				   for:[:year :month :day |
-	^ year
-    ]
+                                   for:[:year :month :day |
+        y := year
+    ].
+    ^ y
+
+    "
+     AbsoluteTime now year
+    "
+!
+
+hours
+    "return the hours (0..23)"
+
+    |hr|
+
+    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
+        :hours :minutes :secs |
+
+        hr := hours
+    ].
+    ^ hr
 
     "
-     Time now year
+     AbsoluteTime now hours 
+    "
+
+!
+
+minutes
+    "return the minutes (0..59)"
+
+    |m|
+
+    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
+        :hours :minutes :secs |
+
+        m := minutes
+    ].
+    ^ m
+
+    "
+     AbsoluteTime now minutes 
     "
+
+!
+
+seconds
+    "return the seconds (0..59)"
+
+    |s|
+
+    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
+        :hours :minutes :secs |
+
+        s := secs
+    ].
+    ^ s
+
+    "
+     AbsoluteTime now seconds 
+    "
+
 ! !
 
 !AbsoluteTime methodsFor:'comparing'!
@@ -229,6 +303,51 @@
     ^ (secondsLow bitShift:16) bitOr:secondsLow
 ! !
 
+!AbsoluteTime methodsFor:'converting'!
+
+asSeconds
+    "return the number of seconds elapsed since whatever time the
+     OperatingSystem bases its time upon. Since this is totally
+     OS-dependent, do not interpret the value returned by this method.
+     You can use it to add/subtract seconds or get time deltas, though."
+
+    ^ (secondsHi * 16r10000) + secondsLow
+
+    "
+     AbsoluteTime now asSeconds
+     AbsoluteTime fromSeconds:(AbsoluteTime now asSeconds + 3600) 
+     Time hour:23 minutes:33 seconds:0         
+     Time fromSeconds:((Time hour:23 minutes:33 seconds:0) asSeconds + 3600) 
+    "
+!
+
+asDate
+    "return a Date object from the receiver"
+
+    ^ Date fromOSTime:(Array with:secondsLow with:secondsHi) 
+
+    "
+     AbsoluteTime now  
+     AbsoluteTime now asDate
+     (AbsoluteTime now addTime:3600) asDate 
+     (AbsoluteTime now addTime:3600) asTime 
+     AbsoluteTime fromSeconds:(AbsoluteTime now asSeconds + 3600) 
+     (AbsoluteTime fromSeconds:(AbsoluteTime now asSeconds + 3600)) asDate  
+    "
+
+!
+
+asTime
+    ^ Time fromOSTime:(Array with:secondsLow with:secondsHi)
+
+    "
+     AbsoluteTime now  
+     AbsoluteTime now asTime
+     (AbsoluteTime now addTime:3600) asTime 
+    "
+
+! !
+
 !AbsoluteTime methodsFor:'arithmetic'!
 
 - aTime
@@ -238,73 +357,61 @@
 !
 
 addTime:timeAmount
-    "return a new Time/Date timeAmount seconds from myself"
+    "return a new instance of myself, timeAmount seconds afterwards"
 
     ^ self class new setSeconds:(self getSeconds + timeAmount)
 !
 
 subtractTime:timeAmount
-    "return a new Time/Date timeAmount seconds before myself"
+    "return a new instance opf myself, timeAmount seconds before myself"
 
     ^ self class new setSeconds:(self getSeconds - timeAmount)
 ! !
 
 !AbsoluteTime methodsFor:'printing & storing'!
 
-storeString
-    |string|
+printOn:aStream
+    |h min s d m y|
 
-    string := '(' , self class name , ' new setSecondsLow:'.
-    string := string , secondsLow storeString.
-    string := string , ' and:' , secondsHi storeString.
-    string := string , ')'.
-    ^ string
-! !
-
-!AbsoluteTime methodsFor:'converting'!
-
-asSeconds
-    "return the number of seconds elapsed since whatever time the
-     OperatingSystem bases its time upon. Since this is totally
-     OS-dependent, do not use this method. (see Time>>asSeconds)"
-
-    ^ (secondsHi * 16r10000) + secondsLow
+    OperatingSystem computeDatePartsOf:secondsLow and:secondsHi for:[
+        :year :month :day | d := day. m := month. y := year.
+    ].
+    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
+        :hours :minutes :secs | h := hours. min := minutes. s := secs.
+    ].
+    d printOn:aStream.
+    aStream nextPut:$-.
+    m printOn:aStream.
+    aStream nextPut:$-.
+    y printOn:aStream.
+    aStream space.
+    h printOn:aStream leftPaddedTo:2 with:$0. 
+    aStream nextPut:$:.
+    min printOn:aStream leftPaddedTo:2 with:$0.
+    aStream nextPut:$:.
+    s printOn:aStream leftPaddedTo:2 with:$0.
 
     "
-     AbsoluteTime asSeconds
+     AbsoluteTime now 
+     AbsoluteTime fromSeconds:0 
+     Time now            
+     Date today         
     "
 !
 
-asDate
-    "return a Date object from the receiver"
+storeOn:aStream
+    aStream nextPut:$(; 
+            nextPutAll:self class name; 
+            nextPutAll:' new setSecondsLow:'.
+    secondsLow storeOn:aStream.
+    aStream nextPutAll:' and:'.
+    secondsHi storeOn:aStream.
+    aStream nextPut:$).
 
-    ^ Date fromOSTime:(Array with:secondsLow with:secondsHi) 
-!
+    "
+     AbsoluteTime now storeString '(AbsoluteTime new setSecondsLow:39757 and:12087)'
 
-asTime
-    ^ Time fromOSTime:(Array with:secondsLow with:secondsHi)
+     AbsoluteTime readFromString:(AbsoluteTime now storeString) 
+    "
 ! !
 
-!AbsoluteTime methodsFor:'private'!
-
-secondsLow
-    ^ secondsLow
-!
-
-secondsHi
-    ^ secondsHi
-!
-
-getSeconds
-    ^ (secondsHi * 16r10000) + secondsLow
-!
-
-setSeconds:secs
-    secondsHi := secs // 16r10000.
-    secondsLow := secs \\ 16r10000
-!
-
-setSecondsLow:secsLow and:secsHi
-    secondsHi := secsHi.
-    secondsLow := secsLow
-! !
--- a/BContext.st	Wed Feb 08 04:10:51 1995 +0100
+++ b/BContext.st	Wed Feb 08 04:11:17 1995 +0100
@@ -21,7 +21,7 @@
 COPYRIGHT (c) 1993 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libbasic/Attic/BContext.st,v 1.10 1995-02-02 12:20:35 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Attic/BContext.st,v 1.11 1995-02-08 03:10:57 claus Exp $
 '!
 
 !BlockContext class methodsFor:'documentation'!
@@ -42,7 +42,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libbasic/Attic/BContext.st,v 1.10 1995-02-02 12:20:35 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Attic/BContext.st,v 1.11 1995-02-08 03:10:57 claus Exp $
 "
 !
 
@@ -118,6 +118,8 @@
 !BlockContext methodsFor:'printing & storing'!
 
 receiverPrintString
+    |cls who|
+
     home isNil ifTrue:[
 	^ '[] optimized'
     ].
@@ -127,8 +129,16 @@
 	"receiverClassName := home selfValue class name."
 	^ '[] optimized'
     ].
-
-    ^ '[] in ' , receiver class name , '-' , self methodHome selector printString
+"/ old:
+"/    cls := receiver class.
+"/ new:
+    who := self methodHome method who.
+    who notNil ifTrue:[
+	cls := who at:1
+    ] ifFalse:[
+	cls := receiver class.
+    ].
+    ^ '[] in ' , cls name , '-' , self methodHome selector printString
 !
 
 printReceiver
--- a/BlockContext.st	Wed Feb 08 04:10:51 1995 +0100
+++ b/BlockContext.st	Wed Feb 08 04:11:17 1995 +0100
@@ -21,7 +21,7 @@
 COPYRIGHT (c) 1993 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libbasic/BlockContext.st,v 1.10 1995-02-02 12:20:35 claus Exp $
+$Header: /cvs/stx/stx/libbasic/BlockContext.st,v 1.11 1995-02-08 03:10:57 claus Exp $
 '!
 
 !BlockContext class methodsFor:'documentation'!
@@ -42,7 +42,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libbasic/BlockContext.st,v 1.10 1995-02-02 12:20:35 claus Exp $
+$Header: /cvs/stx/stx/libbasic/BlockContext.st,v 1.11 1995-02-08 03:10:57 claus Exp $
 "
 !
 
@@ -118,6 +118,8 @@
 !BlockContext methodsFor:'printing & storing'!
 
 receiverPrintString
+    |cls who|
+
     home isNil ifTrue:[
 	^ '[] optimized'
     ].
@@ -127,8 +129,16 @@
 	"receiverClassName := home selfValue class name."
 	^ '[] optimized'
     ].
-
-    ^ '[] in ' , receiver class name , '-' , self methodHome selector printString
+"/ old:
+"/    cls := receiver class.
+"/ new:
+    who := self methodHome method who.
+    who notNil ifTrue:[
+	cls := who at:1
+    ] ifFalse:[
+	cls := receiver class.
+    ].
+    ^ '[] in ' , cls name , '-' , self methodHome selector printString
 !
 
 printReceiver
--- a/Date.st	Wed Feb 08 04:10:51 1995 +0100
+++ b/Date.st	Wed Feb 08 04:11:17 1995 +0100
@@ -22,7 +22,7 @@
 COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libbasic/Date.st,v 1.14 1994-11-17 14:17:23 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Date.st,v 1.15 1995-02-08 03:10:54 claus Exp $
 '!
 
 !Date class methodsFor:'documentation'!
@@ -43,7 +43,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libbasic/Date.st,v 1.14 1994-11-17 14:17:23 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Date.st,v 1.15 1995-02-08 03:10:54 claus Exp $
 "
 !
 
@@ -66,7 +66,7 @@
     Compatibility notice:
 	due to some historic reasons, there are some methods found twice
 	with different names in this class. The old ST/X methods will vanish in
-	on of the next releases, and kept for a while to support existing
+	one of the next releases, and kept for a while to support existing
 	applications (the info on how these methods should be named came 
 	somewhat late from the testers ..).
 
@@ -462,21 +462,16 @@
 
 fromOSTime:osTime
     "return a date, representing the date given by the operatingSystem time.
-     This somewhat clumsy implementation hides the OS's date representation.
+     This somewhat clumsy implementation hides the OS's date representation
+     (i.e. makes this class independent of what the OS starts its time values with).
      Dont use this method, the osTime representation is totally unportable."
 
-    |newDate|
-
-    newDate := Date basicNew.
-    OperatingSystem computeDatePartsOf:osTime 
-				   for:[:year :month :day |
-	newDate dateEncoding:(((year * 100) + month) * 100) + day
-    ].
-    ^ newDate
+    ^ self basicNew fromOSTime:osTime
 
     "
      Date fromOSTime:#(0 0)      -> on UNIX: this should return 1st Jan 1970
 				    thats where Unix time starts
+				    On other systems, it may be something different.
 
      Date fromOSTime:#(86400 0)  -> on UNIX: the day after
     "
@@ -678,6 +673,18 @@
      and should not be used outside."
 
     dateEncoding := anInteger
+!
+
+fromOSTime:osTime
+    "set my dateEncoding from an OS time.
+     This somewhat clumsy implementation hides the OS's date representation
+     (i.e. makes this class independent of what the OS starts its time values with).
+     Dont use this method, the osTime representation is totally unportable."
+
+    OperatingSystem computeDatePartsOf:osTime 
+				   for:[:year :month :day |
+	dateEncoding := (((year * 100) + month) * 100) + day
+    ]
 ! !
 
 !Date methodsFor:'arithmetic'!
--- a/LinkList.st	Wed Feb 08 04:10:51 1995 +0100
+++ b/LinkList.st	Wed Feb 08 04:11:17 1995 +0100
@@ -21,7 +21,7 @@
 COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libbasic/Attic/LinkList.st,v 1.10 1994-10-28 01:24:45 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Attic/LinkList.st,v 1.11 1995-02-08 03:11:01 claus Exp $
 '!
 
 !LinkedList class methodsFor:'documentation'!
@@ -42,7 +42,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libbasic/Attic/LinkList.st,v 1.10 1994-10-28 01:24:45 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Attic/LinkList.st,v 1.11 1995-02-08 03:11:01 claus Exp $
 "
 !
 
@@ -119,7 +119,8 @@
     "return the n'th element - use of this method should be avoided,
      since it is slow to walk through the list - think about using
      another collection if you need index access.
-     Notice, that many methods in SeqColl are based on at:-access."
+     Notice, that many methods in SeqColl are based on at:-access,
+     so other inherited methods may be very slow (showing square runtime)."
 
     |theLink
      runIndex "{Class: SmallInteger}"|
--- a/LinkedList.st	Wed Feb 08 04:10:51 1995 +0100
+++ b/LinkedList.st	Wed Feb 08 04:11:17 1995 +0100
@@ -21,7 +21,7 @@
 COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libbasic/LinkedList.st,v 1.10 1994-10-28 01:24:45 claus Exp $
+$Header: /cvs/stx/stx/libbasic/LinkedList.st,v 1.11 1995-02-08 03:11:01 claus Exp $
 '!
 
 !LinkedList class methodsFor:'documentation'!
@@ -42,7 +42,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libbasic/LinkedList.st,v 1.10 1994-10-28 01:24:45 claus Exp $
+$Header: /cvs/stx/stx/libbasic/LinkedList.st,v 1.11 1995-02-08 03:11:01 claus Exp $
 "
 !
 
@@ -119,7 +119,8 @@
     "return the n'th element - use of this method should be avoided,
      since it is slow to walk through the list - think about using
      another collection if you need index access.
-     Notice, that many methods in SeqColl are based on at:-access."
+     Notice, that many methods in SeqColl are based on at:-access,
+     so other inherited methods may be very slow (showing square runtime)."
 
     |theLink
      runIndex "{Class: SmallInteger}"|
--- a/Make.proto	Wed Feb 08 04:10:51 1995 +0100
+++ b/Make.proto	Wed Feb 08 04:11:17 1995 +0100
@@ -1,4 +1,4 @@
-# $Header: /cvs/stx/stx/libbasic/Make.proto,v 1.19 1995-02-02 12:36:52 claus Exp $
+# $Header: /cvs/stx/stx/libbasic/Make.proto,v 1.20 1995-02-08 03:11:17 claus Exp $
 #
 # -------------- no need to change anything below ----------
 
@@ -65,7 +65,8 @@
 	      Magnitude.$(O)                              \
 		LookupKey.$(O)                            \
 		  Assoc.$(O)                              \
-		AbsTime.$(O)                              \
+		AbstrTime.$(O)                            \
+		  AbsTime.$(O)                            \
 		  Time.$(O)                               \
 		ArithVal.$(O)                             \
 		  Number.$(O)                             \
@@ -154,16 +155,17 @@
 	-rm -f *.c *.H abbrev.stc classList.stc
 
 tar:
-	rm -f $(TOP)/DISTRIB/libbasic.tar*
 	(cd $(TOP); tar cvf DISTRIB/libbasic.tar \
 				libbasic/Make.proto \
 				libbasic/*.st \
 				libbasic/resources)
-	gzip $(TOP)/DISTRIB/libbasic.tar
 
 uutar:
 	$(MAKE) tar
+	gzip $(TOP)/DISTRIB/libbasic.tar
+	-rm $(TOP)/DISTRIB/libbasic.tar
 	(cd $(TOP)/DISTRIB; uuencode libbasic.tar.gz libbasic.tar.gz > libbasic.tar.gz.uue)
+	-rm $(TOP)/DISTRIB/libbasic.tar.gz
 
 
 #
@@ -225,7 +227,7 @@
 Project.$(O):      Project.st $(OBJECT)
 
 MAGNITUDE=$(I)/Magnitude.H $(OBJECT)
-ABSTIME=$(I)/AbsTime.H $(MAGNITUDE)
+ABSTRTIME=$(I)/AbstrTime.H $(MAGNITUDE)
 ARITHVAL=$(I)/ArithVal.H $(MAGNITUDE)
 NUMBER=$(I)/Number.H $(ARITHVAL)
 INTEGER=$(I)/Integer.H $(NUMBER)
@@ -243,9 +245,10 @@
 Fraction.$(O):     Fraction.st $(NUMBER)
 SmallInt.$(O):     SmallInt.st $(INTEGER)
 LargeInt.$(O):     LargeInt.st $(INTEGER)
-AbsTime.$(O):      AbsTime.st $(MAGNITUDE)
-Time.$(O):         Time.st $(ABSTIME)
-Date.$(O):         Date.st $(ABSTIME)
+AbstrTime.$(O):    AbstrTime.st $(MAGNITUDE)
+AbsTime.$(O):      AbsTime.st $(ABSTRTIME)
+Time.$(O):         Time.st $(ABSTRTIME)
+Date.$(O):         Date.st $(MAGNITUDE)
 
 COLL=$(I)/Coll.H $(OBJECT)
 SET=$(I)/Set.H $(COLL)
--- a/MiniDebug.st	Wed Feb 08 04:10:51 1995 +0100
+++ b/MiniDebug.st	Wed Feb 08 04:11:17 1995 +0100
@@ -21,7 +21,7 @@
 COPYRIGHT (c) 1988 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libbasic/Attic/MiniDebug.st,v 1.10 1995-02-02 12:21:24 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Attic/MiniDebug.st,v 1.11 1995-02-08 03:10:59 claus Exp $
 '!
 
 !MiniDebugger class methodsFor: 'documentation'!
@@ -42,7 +42,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libbasic/Attic/MiniDebug.st,v 1.10 1995-02-02 12:21:24 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Attic/MiniDebug.st,v 1.11 1995-02-08 03:10:59 claus Exp $
 "
 !
 
@@ -70,10 +70,10 @@
     |aDebugger|
 
     aDebugger := self new stepping.
+    ObjectMemory stepInterruptHandler:aDebugger.
     ObjectMemory flushInlineCaches.
-    ObjectMemory stepInterruptHandler:aDebugger.
-    StepInterruptPending := true.
-    InterruptPending := true.
+    StepInterruptPending := 1.
+    InterruptPending := 1.
     aBlock value.
     StepInterruptPending := nil.
     ObjectMemory stepInterruptHandler:nil
@@ -92,10 +92,10 @@
     |aDebugger|
 
     aDebugger := self new tracingWith:aTraceBlock.
+    ObjectMemory stepInterruptHandler:aDebugger.
     ObjectMemory flushInlineCaches.
-    ObjectMemory stepInterruptHandler:aDebugger.
-    StepInterruptPending := true.
-    InterruptPending := true.
+    StepInterruptPending := 1.
+    InterruptPending := 1.
     aBlock value.
     ObjectMemory stepInterruptHandler:nil.
     StepInterruptPending := nil.
@@ -205,8 +205,8 @@
 	    'traceInterrupt: no context' errorPrintNewline
 	].
 	ObjectMemory flushInlineCaches.
-	StepInterruptPending := true.
-	InterruptPending := true
+	StepInterruptPending := 1.
+	InterruptPending := 1
     ]
 !
 
@@ -222,16 +222,16 @@
 	    ObjectMemory flushInlineCaches.
 	    ObjectMemory stepInterruptHandler:self.
 	    stillHere := false.
-	    StepInterruptPending := true.
-	    InterruptPending := true
+	    StepInterruptPending := 1.
+	    InterruptPending := 1
 	].
 	(leaveCmd == $t) ifTrue: [
 	    traceBlock := [:where | where fullPrint].
 	    ObjectMemory flushInlineCaches.
 	    ObjectMemory stepInterruptHandler:self.
 	    stillHere := false.
-	    StepInterruptPending := true.
-	    InterruptPending := true
+	    StepInterruptPending := 1.
+	    InterruptPending := 1
 	].
 	(leaveCmd == $c) ifTrue: [
 	    stillHere := false.
--- a/MiniDebugger.st	Wed Feb 08 04:10:51 1995 +0100
+++ b/MiniDebugger.st	Wed Feb 08 04:11:17 1995 +0100
@@ -21,7 +21,7 @@
 COPYRIGHT (c) 1988 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libbasic/MiniDebugger.st,v 1.10 1995-02-02 12:21:24 claus Exp $
+$Header: /cvs/stx/stx/libbasic/MiniDebugger.st,v 1.11 1995-02-08 03:10:59 claus Exp $
 '!
 
 !MiniDebugger class methodsFor: 'documentation'!
@@ -42,7 +42,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libbasic/MiniDebugger.st,v 1.10 1995-02-02 12:21:24 claus Exp $
+$Header: /cvs/stx/stx/libbasic/MiniDebugger.st,v 1.11 1995-02-08 03:10:59 claus Exp $
 "
 !
 
@@ -70,10 +70,10 @@
     |aDebugger|
 
     aDebugger := self new stepping.
+    ObjectMemory stepInterruptHandler:aDebugger.
     ObjectMemory flushInlineCaches.
-    ObjectMemory stepInterruptHandler:aDebugger.
-    StepInterruptPending := true.
-    InterruptPending := true.
+    StepInterruptPending := 1.
+    InterruptPending := 1.
     aBlock value.
     StepInterruptPending := nil.
     ObjectMemory stepInterruptHandler:nil
@@ -92,10 +92,10 @@
     |aDebugger|
 
     aDebugger := self new tracingWith:aTraceBlock.
+    ObjectMemory stepInterruptHandler:aDebugger.
     ObjectMemory flushInlineCaches.
-    ObjectMemory stepInterruptHandler:aDebugger.
-    StepInterruptPending := true.
-    InterruptPending := true.
+    StepInterruptPending := 1.
+    InterruptPending := 1.
     aBlock value.
     ObjectMemory stepInterruptHandler:nil.
     StepInterruptPending := nil.
@@ -205,8 +205,8 @@
 	    'traceInterrupt: no context' errorPrintNewline
 	].
 	ObjectMemory flushInlineCaches.
-	StepInterruptPending := true.
-	InterruptPending := true
+	StepInterruptPending := 1.
+	InterruptPending := 1
     ]
 !
 
@@ -222,16 +222,16 @@
 	    ObjectMemory flushInlineCaches.
 	    ObjectMemory stepInterruptHandler:self.
 	    stillHere := false.
-	    StepInterruptPending := true.
-	    InterruptPending := true
+	    StepInterruptPending := 1.
+	    InterruptPending := 1
 	].
 	(leaveCmd == $t) ifTrue: [
 	    traceBlock := [:where | where fullPrint].
 	    ObjectMemory flushInlineCaches.
 	    ObjectMemory stepInterruptHandler:self.
 	    stillHere := false.
-	    StepInterruptPending := true.
-	    InterruptPending := true
+	    StepInterruptPending := 1.
+	    InterruptPending := 1
 	].
 	(leaveCmd == $c) ifTrue: [
 	    stillHere := false.
--- a/ProcSched.st	Wed Feb 08 04:10:51 1995 +0100
+++ b/ProcSched.st	Wed Feb 08 04:11:17 1995 +0100
@@ -23,6 +23,7 @@
 			     UserSchedulingPriority 
 			     UserInterruptPriority
 			     TimingPriority
+			     HighestPriority
 			     SchedulingPriority'
 	 poolDictionaries:''
 	 category:'Kernel-Processes'
@@ -32,7 +33,7 @@
 COPYRIGHT (c) 1993 by Claus Gittinger
 	     All Rights Reserved
 
-$Header: /cvs/stx/stx/libbasic/Attic/ProcSched.st,v 1.27 1995-02-05 21:33:24 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Attic/ProcSched.st,v 1.28 1995-02-08 03:11:03 claus Exp $
 '!
 
 Smalltalk at:#Processor put:nil!
@@ -55,7 +56,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libbasic/Attic/ProcSched.st,v 1.27 1995-02-05 21:33:24 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Attic/ProcSched.st,v 1.28 1995-02-08 03:11:03 claus Exp $
 "
 !
 
@@ -91,19 +92,26 @@
 
 	KnownProcesses          <Collection>    all known processes
 	KnownProcessIds         <Collection>    and their IDs
+
 	PureEventDriven         <Boolean>       true, if no process support
 						is available
+
 	UserSchedulingPriority  <Integer>       the priority at which normal
 						user interfaces run
+
 	UserInterruptPriority                   the priority at which user-
 						interrupts (Cntl-C) processing
 						takes place. Processes with
 						a greater or equal priority are
 						not interruptable.
+
 	TimingPriority                          the priority used for timing.
 						Processes with a greater or
 						equal priority are not interrupted
 						by timers.
+
+	HighestPriority                         The highest allowed prio for processes
+
 	SchedulingPriority                      The priority of the scheduler (must
 						me higher than any other).
 
@@ -134,6 +142,7 @@
     UserInterruptPriority := 24.
     TimingPriority := 16.
     SchedulingPriority := 31.
+    HighestPriority := 30.
 
     Processor isNil ifTrue:[
 	"create the one and only processor"
@@ -306,12 +315,9 @@
     activeProcess := aProcess.
     currentPriority := pri.
 %{
-    extern OBJ __threadSwitch(), __threadSwitchWithSingleStep();
+    extern OBJ ___threadSwitch();
 
-    if (singleStep == true)
-	ok = __threadSwitchWithSingleStep(__context, _intVal(id));
-    else
-	ok = __threadSwitch(__context, _intVal(id));
+    ok = ___threadSwitch(__context, _intVal(id), (singleStep == true) ? 1 : 0);
 %}.
     "time passes spent in some other process ...
      ... here again"
@@ -368,7 +374,7 @@
     "must be below schedulingPriority - 
      otherwise scheduler could be blocked ...
     "
-    ^ SchedulingPriority - 1  
+    ^ HighestPriority  
 !
 
 schedulingPriority
@@ -602,16 +608,16 @@
      check if the running process is not the only one
     "
     l size ~~ 1 ifTrue:[
-        "
-         bring running process to the end
-        "
-        l removeFirst.
-        l addLast:activeProcess.
+	"
+	 bring running process to the end
+	"
+	l removeFirst.
+	l addLast:activeProcess.
 
-        "
-         and switch to first in the list
-        "
-        self threadSwitch:(l first).
+	"
+	 and switch to first in the list
+	"
+	self threadSwitch:(l first).
     ].
     wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
 !
@@ -877,8 +883,8 @@
 	newPrio := 1.
     ] ifFalse:[
 	aProcess == scheduler ifTrue:[^ self].
-	newPrio >= SchedulingPriority ifTrue:[
-	    newPrio := SchedulingPriority - 1
+	newPrio > HighestPriority ifTrue:[
+	    newPrio := HighestPriority
 	]
     ].
 
@@ -954,17 +960,18 @@
 highestPriorityRunnableProcess
     "return the highest prio runnable process"
 
-    |l p maxPri "{ Class: SmallInteger }" |
+    |listArray l p maxPri "{ Class: SmallInteger }" |
 
-    maxPri := self highestPriority.
+    maxPri := HighestPriority.
+    listArray := quiescentProcessLists.
     maxPri to:1 by:-1 do:[:prio |
-	l := quiescentProcessLists at:prio.
+	l := listArray at:prio.
 	l notNil ifTrue:[
 	    l isEmpty ifTrue:[
 		"
 		 on the fly clear out empty lists
 		"
-		quiescentProcessLists at:prio put:nil
+		listArray at:prio put:nil
 	    ] ifFalse:[    
 		p := l first.
 		"
@@ -982,18 +989,27 @@
     ^ nil
 !
 
+isSystemProcess:aProcess
+    "return true if aProcess is a system process,
+     which should not be suspended/terminated etc.."
+
+    (self class isPureEventDriven 
+    or:[aProcess id == 0
+    or:[aProcess nameOrId endsWith:'dispatcher']]) ifTrue:[
+	^ true
+    ].
+    ^ false
+
+    "
+     Processor activeProcessIsSystemProcess
+    "
+!
+
 activeProcessIsSystemProcess
     "return true if the active process is a system process,
      which should not be suspended."
 
-    |active|
-
-    (self class isPureEventDriven 
-    or:[(active := self activeProcess) id == 0
-    or:[active nameOrId endsWith:'dispatcher']]) ifTrue:[
-	^ true
-    ].
-    ^ false
+    ^ self isSystemProcess:activeProcess
 
     "
      Processor activeProcessIsSystemProcess
--- a/ProcessorScheduler.st	Wed Feb 08 04:10:51 1995 +0100
+++ b/ProcessorScheduler.st	Wed Feb 08 04:11:17 1995 +0100
@@ -23,6 +23,7 @@
 			     UserSchedulingPriority 
 			     UserInterruptPriority
 			     TimingPriority
+			     HighestPriority
 			     SchedulingPriority'
 	 poolDictionaries:''
 	 category:'Kernel-Processes'
@@ -32,7 +33,7 @@
 COPYRIGHT (c) 1993 by Claus Gittinger
 	     All Rights Reserved
 
-$Header: /cvs/stx/stx/libbasic/ProcessorScheduler.st,v 1.27 1995-02-05 21:33:24 claus Exp $
+$Header: /cvs/stx/stx/libbasic/ProcessorScheduler.st,v 1.28 1995-02-08 03:11:03 claus Exp $
 '!
 
 Smalltalk at:#Processor put:nil!
@@ -55,7 +56,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libbasic/ProcessorScheduler.st,v 1.27 1995-02-05 21:33:24 claus Exp $
+$Header: /cvs/stx/stx/libbasic/ProcessorScheduler.st,v 1.28 1995-02-08 03:11:03 claus Exp $
 "
 !
 
@@ -91,19 +92,26 @@
 
 	KnownProcesses          <Collection>    all known processes
 	KnownProcessIds         <Collection>    and their IDs
+
 	PureEventDriven         <Boolean>       true, if no process support
 						is available
+
 	UserSchedulingPriority  <Integer>       the priority at which normal
 						user interfaces run
+
 	UserInterruptPriority                   the priority at which user-
 						interrupts (Cntl-C) processing
 						takes place. Processes with
 						a greater or equal priority are
 						not interruptable.
+
 	TimingPriority                          the priority used for timing.
 						Processes with a greater or
 						equal priority are not interrupted
 						by timers.
+
+	HighestPriority                         The highest allowed prio for processes
+
 	SchedulingPriority                      The priority of the scheduler (must
 						me higher than any other).
 
@@ -134,6 +142,7 @@
     UserInterruptPriority := 24.
     TimingPriority := 16.
     SchedulingPriority := 31.
+    HighestPriority := 30.
 
     Processor isNil ifTrue:[
 	"create the one and only processor"
@@ -306,12 +315,9 @@
     activeProcess := aProcess.
     currentPriority := pri.
 %{
-    extern OBJ __threadSwitch(), __threadSwitchWithSingleStep();
+    extern OBJ ___threadSwitch();
 
-    if (singleStep == true)
-	ok = __threadSwitchWithSingleStep(__context, _intVal(id));
-    else
-	ok = __threadSwitch(__context, _intVal(id));
+    ok = ___threadSwitch(__context, _intVal(id), (singleStep == true) ? 1 : 0);
 %}.
     "time passes spent in some other process ...
      ... here again"
@@ -368,7 +374,7 @@
     "must be below schedulingPriority - 
      otherwise scheduler could be blocked ...
     "
-    ^ SchedulingPriority - 1  
+    ^ HighestPriority  
 !
 
 schedulingPriority
@@ -602,16 +608,16 @@
      check if the running process is not the only one
     "
     l size ~~ 1 ifTrue:[
-        "
-         bring running process to the end
-        "
-        l removeFirst.
-        l addLast:activeProcess.
+	"
+	 bring running process to the end
+	"
+	l removeFirst.
+	l addLast:activeProcess.
 
-        "
-         and switch to first in the list
-        "
-        self threadSwitch:(l first).
+	"
+	 and switch to first in the list
+	"
+	self threadSwitch:(l first).
     ].
     wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
 !
@@ -877,8 +883,8 @@
 	newPrio := 1.
     ] ifFalse:[
 	aProcess == scheduler ifTrue:[^ self].
-	newPrio >= SchedulingPriority ifTrue:[
-	    newPrio := SchedulingPriority - 1
+	newPrio > HighestPriority ifTrue:[
+	    newPrio := HighestPriority
 	]
     ].
 
@@ -954,17 +960,18 @@
 highestPriorityRunnableProcess
     "return the highest prio runnable process"
 
-    |l p maxPri "{ Class: SmallInteger }" |
+    |listArray l p maxPri "{ Class: SmallInteger }" |
 
-    maxPri := self highestPriority.
+    maxPri := HighestPriority.
+    listArray := quiescentProcessLists.
     maxPri to:1 by:-1 do:[:prio |
-	l := quiescentProcessLists at:prio.
+	l := listArray at:prio.
 	l notNil ifTrue:[
 	    l isEmpty ifTrue:[
 		"
 		 on the fly clear out empty lists
 		"
-		quiescentProcessLists at:prio put:nil
+		listArray at:prio put:nil
 	    ] ifFalse:[    
 		p := l first.
 		"
@@ -982,18 +989,27 @@
     ^ nil
 !
 
+isSystemProcess:aProcess
+    "return true if aProcess is a system process,
+     which should not be suspended/terminated etc.."
+
+    (self class isPureEventDriven 
+    or:[aProcess id == 0
+    or:[aProcess nameOrId endsWith:'dispatcher']]) ifTrue:[
+	^ true
+    ].
+    ^ false
+
+    "
+     Processor activeProcessIsSystemProcess
+    "
+!
+
 activeProcessIsSystemProcess
     "return true if the active process is a system process,
      which should not be suspended."
 
-    |active|
-
-    (self class isPureEventDriven 
-    or:[(active := self activeProcess) id == 0
-    or:[active nameOrId endsWith:'dispatcher']]) ifTrue:[
-	^ true
-    ].
-    ^ false
+    ^ self isSystemProcess:activeProcess
 
     "
      Processor activeProcessIsSystemProcess
--- a/Time.st	Wed Feb 08 04:10:51 1995 +0100
+++ b/Time.st	Wed Feb 08 04:11:17 1995 +0100
@@ -10,18 +10,20 @@
  hereby transferred.
 "
 
+'From Smalltalk/X, Version:2.10.4 on 8-feb-1995 at 12:46:41 pm'!
+
 AbsoluteTime subclass:#Time
-       instanceVariableNames:''
-       classVariableNames:''
-       poolDictionaries:''
-       category:'Magnitude-General'
+	 instanceVariableNames:'timeEncoding'
+	 classVariableNames:''
+	 poolDictionaries:''
+	 category:'Magnitude-General'
 !
 
 Time comment:'
 COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libbasic/Time.st,v 1.13 1995-02-06 02:56:44 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Time.st,v 1.14 1995-02-08 03:11:08 claus Exp $
 '!
 
 !Time class methodsFor:'documentation'!
@@ -42,13 +44,30 @@
 
 version
 "
-$Header: /cvs/stx/stx/libbasic/Time.st,v 1.13 1995-02-06 02:56:44 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Time.st,v 1.14 1995-02-08 03:11:08 claus Exp $
 "
 !
 
 documentation
 "
     Instances of time represent a particular time-of-day.
+    Since they only store hours, minutes and seconds of a day,
+    they cannot be used to compare times across midnight.
+    Use instances of AbsoluteTime (and read the comment there) to do this.
+
+    Examples:
+        |t|
+
+        t := Time now.
+        Transcript showCr:t.
+
+
+        |t1 t2|
+
+        t1 := Time now.
+        (Delay forSeconds:10) wait.
+        t2 := Time now.
+        t2 - t1   
 "
 ! !
 
@@ -67,37 +86,34 @@
 hour:h minutes:m seconds:s
     "return an instance of Time representing the given values"
 
-    | seconds |
+    |seconds|
 
-    "have to subtract 3600; unix time starts at 1'o clock"
-    seconds := (h * 60 * 60 ) + (m * 60) + s - 3600.
+    seconds := ((h\\24) * 60 * 60 ) + (m * 60) + s.
 
-    ^ self basicNew setSeconds:seconds.
+    ^ self basicNew timeEncoding:seconds.
 
     "
      Time hour:2 minutes:33 seconds:0 
-    "
-!
-
-fromSeconds:seconds
-    "return a Time that is constructed from seconds since midnight."
-
-    "have to subtract 3600; unix time starts at 1'o clock"
-   ^ self basicNew setSeconds:seconds-3600
-
-    "
-     Time fromSeconds:0
+     Time hour:0 minutes:0 seconds:0 
+     Time hour:24 minutes:0 seconds:0 
+     Time hour:23 minutes:59 seconds:59 
     "
 !
 
 fromOSTime:osTime
     "return a time, representing the time given by the operatingSystem time"
 
-    ^ self basicNew setSecondsLow:(osTime at:1) and:(osTime at:2)
+    OperatingSystem computeTimePartsOf:(osTime at:1) and:(osTime at:2) for:[
+        :hours :minutes :secs |
+
+        ^ self hour:hours minutes:minutes seconds:secs
+    ]
 !
 
 readFrom:aStream onError:exceptionBlock
-    "return a new Time, reading a printed representation from aStream."
+    "return a new Time, reading a printed representation from aStream.
+     If no pm follows the time, the string is interpreted as either 24 hour format
+     or being am."
 
     |hour min sec|
 
@@ -108,8 +124,8 @@
     sec := Integer readFrom:aStream onError:[^ exceptionBlock value].
     [aStream peek == Character space] whileTrue:[aStream next].
     (aStream peek == $p) ifTrue:[
-	"pm"
-	hour := hour + 12
+        "pm"
+        hour := hour + 12
     ].
     ^ self hour:hour minutes:min seconds:sec
 
@@ -122,6 +138,16 @@
      Time readFromString:'7:00:11 am'  
     "
 
+!
+
+fromSeconds:seconds
+    "return a Time that is constructed from seconds since midnight."
+
+   ^ self basicNew timeEncoding:seconds
+
+    "
+     Time fromSeconds:0
+    "
 ! !
 
 !Time class methodsFor:'ST-80 compatibility'!
@@ -130,39 +156,12 @@
     ^ self secondClock
 ! !
 
-
 !Time methodsFor:'accessing'!
 
-asSeconds
-    "return the number of seconds elapsed since midnight"
-
-    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
-	:hours :minutes :seconds |
-
-	^ ( 3600 * hours   )
-	  + ( 60 * minutes )
-	  + seconds
-    ]
-
-    "
-     Time now asSeconds
-    "
-!
-
-hours
-    "return the number of hours since midnight (i.e. 0..23)"
-
-    ^ self hourInDay
-
-    "
-     Time now hours
-    "
-!
-
 minutes
     "return the number of minutes within the hour (i.e. 0..59)"
 
-    ^self minuteInDay
+    ^ (timeEncoding \\ 3600) // 60
 
     "
      Time now minutes
@@ -172,37 +171,21 @@
 seconds
     "return the number of seconds within the minute (i.e. 0..59)"
 
-    ^self secondInDay
+    ^ (timeEncoding \\ 3600) \\ 60
 
     "
      Time now seconds
     "
-! !
-
-!Time methodsFor:'comparing'!
-
-> aTime
-    "return true if the argument, aTime is after the receiver"
-
-    (aTime respondsTo:#secondsLow) ifTrue:[
-	(secondsHi > aTime secondsHi) ifTrue:[^ true].
-	(secondsHi < aTime secondsHi) ifTrue:[^ false].
-	(secondsLow > aTime secondsLow) ifTrue:[^ true].
-	^ false
-    ].
-    ^ self getSeconds > aTime getSeconds
 !
 
-< aTime
-    "return true if the argument, aTime is before the receiver"
+hours
+    "return the number of hours since midnight (i.e. 0..23)"
 
-    (aTime respondsTo:#secondsLow) ifTrue:[
-	(secondsHi < aTime secondsHi) ifTrue:[^ true].
-	(secondsHi > aTime secondsHi) ifTrue:[^ false].
-	(secondsLow < aTime secondsLow) ifTrue:[^ true].
-	^ false
-    ].
-    ^ self getSeconds < aTime getSeconds
+    ^ timeEncoding // 3600
+
+    "
+     Time now hours
+    "
 ! !
 
 !Time methodsFor:'printing & storing'!
@@ -228,17 +211,17 @@
     "append a printed representation of the receiver to aStream.
      Format is hh:mm:ss in 24-hour format."
 
-    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
-	:hours :minutes :secs |
+    |m s|
 
-	hours printOn:aStream.
-	aStream nextPut:$:.
-	(minutes < 10) ifTrue:[aStream nextPut:$0].
-	minutes printOn:aStream.
-	aStream nextPut:$:.
-	(secs < 10) ifTrue:[aStream nextPut:$0].
-	secs printOn:aStream
-    ]
+    self hours printOn:aStream.
+    aStream nextPut:$:.
+    m := self minutes.
+    (m < 10) ifTrue:[aStream nextPut:$0].
+    m printOn:aStream.
+    aStream nextPut:$:.
+    s := self seconds.
+    (s < 10) ifTrue:[aStream nextPut:$0].
+    s printOn:aStream
 
     "
      Time now print24HourFormatOn:Transcript. Transcript cr
@@ -247,34 +230,83 @@
 
 print12HourFormatOn:aStream
     "append a printed representation of the receiver to aStream.
-     Format is hh:mm:ss am/pm (i.e. 12-hour format)."
+     Format is hh:mm:ss am/pm (i.e. 12-hour american format)."
 
-    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
-	:hours :minutes :secs | |h|
+    |h m s|
 
-	h := hours.
-	h > 12 ifTrue:[
-	    h := h - 12.
-	] ifFalse:[
-	    h < 1 ifTrue:[
-		h := 12
-	    ]
-	].
-	h printOn:aStream.
-	aStream nextPut:$:.
-	(minutes < 10) ifTrue:[aStream nextPut:$0].
-	minutes printOn:aStream.
-	aStream nextPut:$:.
-	(secs < 10) ifTrue:[aStream nextPut:$0].
-	secs printOn:aStream.
-	hours >= 12 ifTrue:[
-	    aStream nextPutAll:' pm'
-	] ifFalse:[
-	    aStream nextPutAll:' am'
-	]
+    h := self hours.
+    h > 12 ifTrue:[
+        h := h - 12.
+    ] ifFalse:[
+        h < 1 ifTrue:[
+            h := 12
+        ]
+    ].
+    h printOn:aStream.
+    aStream nextPut:$:.
+    m := self minutes.
+    (m < 10) ifTrue:[aStream nextPut:$0].
+    m printOn:aStream.
+    aStream nextPut:$:.
+    s := self seconds.
+    (s < 10) ifTrue:[aStream nextPut:$0].
+        s printOn:aStream.
+    h >= 12 ifTrue:[
+        aStream nextPutAll:' pm'
+    ] ifFalse:[
+        aStream nextPutAll:' am'
     ]
 
     "
      Time now print12HourFormatOn:Transcript. Transcript cr
     "
 ! !
+
+!Time methodsFor:'converting'!
+
+asSeconds
+    "return the number of seconds elapsed since midnight"
+
+    ^ timeEncoding
+
+    "
+     Time now asSeconds
+    "
+! !
+
+!Time methodsFor:'comparing'!
+
+> aTime
+    "return true if the argument, aTime is after the receiver"
+
+    (aTime respondsTo:#timeEncoding) ifTrue:[
+        ^ timeEncoding > aTime timeEncoding
+    ].
+    ^ self getSeconds > aTime getSeconds
+!
+
+< aTime
+    "return true if the argument, aTime is before the receiver"
+
+    (aTime respondsTo:#timeEncoding) ifTrue:[
+        ^ timeEncoding < aTime timeEncoding
+    ].
+    ^ self getSeconds < aTime getSeconds
+! !
+
+!Time methodsFor:'private'!
+
+timeEncoding:encoding
+    "the internal encoding is stricktly private, 
+     and should not be used outside."
+
+    timeEncoding := encoding
+!
+
+timeEncoding
+    "the internal encoding is stricktly private, 
+     and should not be used outside."
+
+    ^ timeEncoding
+! !
+
--- a/Timestamp.st	Wed Feb 08 04:10:51 1995 +0100
+++ b/Timestamp.st	Wed Feb 08 04:11:17 1995 +0100
@@ -10,18 +10,20 @@
  hereby transferred.
 "
 
-Magnitude subclass:#AbsoluteTime
-       instanceVariableNames:'secondsLow secondsHi'
-       classVariableNames:''
-       poolDictionaries:''
-       category:'Magnitude-General'
+'From Smalltalk/X, Version:2.10.4 on 8-feb-1995 at 12:46:45 pm'!
+
+AbstractTime subclass:#AbsoluteTime
+	 instanceVariableNames:'secondsLow secondsHi'
+	 classVariableNames:''
+	 poolDictionaries:''
+	 category:'Magnitude-General'
 !
 
 AbsoluteTime comment:'
 COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libbasic/Timestamp.st,v 1.7 1994-11-28 20:32:07 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Timestamp.st,v 1.8 1995-02-08 03:10:47 claus Exp $
 '!
 
 !AbsoluteTime class methodsFor:'documentation'!
@@ -42,7 +44,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libbasic/Timestamp.st,v 1.7 1994-11-28 20:32:07 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Timestamp.st,v 1.8 1995-02-08 03:10:47 claus Exp $
 "
 !
 
@@ -51,9 +53,10 @@
     This class represents time values in seconds from 1st. Jan 1970, as
     used in the Unix operating system. Its implementation is not the same
     as in ST-80 (which represents Time as seconds from 1. Jan 1901.
-    Actually, the implementation does not even know which time/date the
-    OperatingSystem bases its time upon - it is simply keeping the value(s)
-    as return from the OS when asked for the time.
+
+    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 return 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 time-stamps on files (such as last-access-
@@ -64,76 +67,74 @@
     we keep low and hi 16bits of the time separately (it could have been 
     implemented using LargeIntegers though).
 
-    This class is typically abstract (it does not have to be, though).
+    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 AbsoluteTime can.
+
     See Time for more details.
 "
 ! !
 
 !AbsoluteTime class methodsFor:'instance creation'!
 
-secondClock
-    "return seconds of now - for GNU-ST compatibility"
+day:d month:m year:y hour:h minutes:min seconds:s
+    "return an instance of the receiver"
 
-    ^ OperatingSystem getTime
-!
+    ^ self fromOSTime:(OperatingSystem 
+                        computeTimePartsFromYear:y month:m day:d 
+                                            hour:h minute:min seconds:s)
 
-millisecondClockValue
-    "return the millisecond clock - since this one overruns
-     regularly, use only for short timing deltas."
+    "
+     AbsoluteTime day:2 month:1 year:1991 hour:12 minutes:30 seconds:0 
+     AbsoluteTime day:8 month:1 year:1995 hour:0 minutes:43 seconds:48 
+    "
+! !
 
-    ^ OperatingSystem getMillisecondTime.
-!
+!AbsoluteTime methodsFor:'private'!
 
-fromUnixTimeLow:low and:hi
-    "return an instance of Time, given the unix time.
-     Internal interface - not for public use."
-
-    ^ self basicNew setSecondsLow:low and:hi
+secondsLow
+    ^ secondsLow
 !
 
-dateAndTimeNow
-    "return an array filled with date and time"
-
-    ^ Array with:(Date today) with:(Time now)
-! !
-
-!AbsoluteTime class methodsFor:'timing evaluations'!
+setSecondsLow:secsLow and:secsHi
+    secondsHi := secsHi.
+    secondsLow := secsLow
+!
 
-secondsToRun:aBlock
-    "evaluate the argument, aBlock; return the number of seconds it took"
-
-    |startTime endTime|
-
-    startTime := self now.
-    aBlock value.
-    endTime := self now.
-    ^ endTime - startTime
+fromOSTimeLow:secsLow and:secsHi
+    secondsHi := secsHi.
+    secondsLow := secsLow
 !
 
-millisecondsToRun:aBlock
-    "evaluate the argument, aBlock; return the number of milliseconds it took"
-
-    |startTime endTime|
+secondsHi
+    ^ secondsHi
+!
 
-    startTime := self millisecondClockValue.
-    aBlock value.
-    endTime := self millisecondClockValue.
-    ^ endTime - startTime
+setSeconds:secs
+    secondsHi := secs // 16r10000.
+    secondsLow := secs \\ 16r10000
+!
+
+getSeconds
+    ^ (secondsHi * 16r10000) + secondsLow
+!
+
+fromOSTime:secs
+    secondsHi := secs // 16r10000.
+    secondsLow := secs \\ 16r10000
 ! !
 
 !AbsoluteTime methodsFor:'accessing'!
 
 hourInDay
-    "return the hour-part"
+    "return the hours (0..23)"
 
-    |hr|
+    ^ self hours
 
-    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
-	:hours :minutes :secs |
+    "
+     AbsoluteTime now hours 
+    "
 
-	hr := hours
-    ].
-    ^ hr
 !
 
 minuteInDay
@@ -142,11 +143,16 @@
     |m|
 
     OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
-	:hours :minutes :secs |
+        :hours :minutes :secs |
 
-	m := minutes
+        m := minutes
     ].
     ^ m
+
+    "
+     AbsoluteTime now minuteInDay 
+    "
+
 !
 
 secondInDay
@@ -155,24 +161,32 @@
     |s|
 
     OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
-	:hours :minutes :secs |
+        :hours :minutes :secs |
 
-	s := secs
+        s := secs
     ].
     ^ s
+
+    "
+     AbsoluteTime now secondInDay 
+    "
+
 !
 
 day
     "return the day-in-month of the receiver (1..31).
      Obsolete; use instances of Date for this."
 
+    |d|
+
     OperatingSystem computeDatePartsOf:secondsLow and:secondsHi
-				   for:[:year :month :day |
-	^ day
-    ]
+                                   for:[:year :month :day |
+        d := day
+    ].
+    ^ d
 
     "
-     Time now day
+     AbsoluteTime now day 
     "
 !
 
@@ -180,13 +194,16 @@
     "return the month of the receiver (1..12).
      Obsolete; use instances of Date for this."
 
+    |m|
+
     OperatingSystem computeDatePartsOf:secondsLow and:secondsHi
-				   for:[:year :month :day |
-	^ month
-    ]
+                                   for:[:year :month :day |
+        m := month
+    ].
+    ^ m
 
     "
-     Time now month
+     AbsoluteTime now month
     "
 !
 
@@ -194,14 +211,71 @@
     "return the year of the receiver i.e. 1992.
      Obsolete; use instances of Date for this."
 
+    |y|
+
     OperatingSystem computeDatePartsOf:secondsLow and:secondsHi
-				   for:[:year :month :day |
-	^ year
-    ]
+                                   for:[:year :month :day |
+        y := year
+    ].
+    ^ y
+
+    "
+     AbsoluteTime now year
+    "
+!
+
+hours
+    "return the hours (0..23)"
+
+    |hr|
+
+    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
+        :hours :minutes :secs |
+
+        hr := hours
+    ].
+    ^ hr
 
     "
-     Time now year
+     AbsoluteTime now hours 
+    "
+
+!
+
+minutes
+    "return the minutes (0..59)"
+
+    |m|
+
+    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
+        :hours :minutes :secs |
+
+        m := minutes
+    ].
+    ^ m
+
+    "
+     AbsoluteTime now minutes 
     "
+
+!
+
+seconds
+    "return the seconds (0..59)"
+
+    |s|
+
+    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
+        :hours :minutes :secs |
+
+        s := secs
+    ].
+    ^ s
+
+    "
+     AbsoluteTime now seconds 
+    "
+
 ! !
 
 !AbsoluteTime methodsFor:'comparing'!
@@ -229,6 +303,51 @@
     ^ (secondsLow bitShift:16) bitOr:secondsLow
 ! !
 
+!AbsoluteTime methodsFor:'converting'!
+
+asSeconds
+    "return the number of seconds elapsed since whatever time the
+     OperatingSystem bases its time upon. Since this is totally
+     OS-dependent, do not interpret the value returned by this method.
+     You can use it to add/subtract seconds or get time deltas, though."
+
+    ^ (secondsHi * 16r10000) + secondsLow
+
+    "
+     AbsoluteTime now asSeconds
+     AbsoluteTime fromSeconds:(AbsoluteTime now asSeconds + 3600) 
+     Time hour:23 minutes:33 seconds:0         
+     Time fromSeconds:((Time hour:23 minutes:33 seconds:0) asSeconds + 3600) 
+    "
+!
+
+asDate
+    "return a Date object from the receiver"
+
+    ^ Date fromOSTime:(Array with:secondsLow with:secondsHi) 
+
+    "
+     AbsoluteTime now  
+     AbsoluteTime now asDate
+     (AbsoluteTime now addTime:3600) asDate 
+     (AbsoluteTime now addTime:3600) asTime 
+     AbsoluteTime fromSeconds:(AbsoluteTime now asSeconds + 3600) 
+     (AbsoluteTime fromSeconds:(AbsoluteTime now asSeconds + 3600)) asDate  
+    "
+
+!
+
+asTime
+    ^ Time fromOSTime:(Array with:secondsLow with:secondsHi)
+
+    "
+     AbsoluteTime now  
+     AbsoluteTime now asTime
+     (AbsoluteTime now addTime:3600) asTime 
+    "
+
+! !
+
 !AbsoluteTime methodsFor:'arithmetic'!
 
 - aTime
@@ -238,73 +357,61 @@
 !
 
 addTime:timeAmount
-    "return a new Time/Date timeAmount seconds from myself"
+    "return a new instance of myself, timeAmount seconds afterwards"
 
     ^ self class new setSeconds:(self getSeconds + timeAmount)
 !
 
 subtractTime:timeAmount
-    "return a new Time/Date timeAmount seconds before myself"
+    "return a new instance opf myself, timeAmount seconds before myself"
 
     ^ self class new setSeconds:(self getSeconds - timeAmount)
 ! !
 
 !AbsoluteTime methodsFor:'printing & storing'!
 
-storeString
-    |string|
+printOn:aStream
+    |h min s d m y|
 
-    string := '(' , self class name , ' new setSecondsLow:'.
-    string := string , secondsLow storeString.
-    string := string , ' and:' , secondsHi storeString.
-    string := string , ')'.
-    ^ string
-! !
-
-!AbsoluteTime methodsFor:'converting'!
-
-asSeconds
-    "return the number of seconds elapsed since whatever time the
-     OperatingSystem bases its time upon. Since this is totally
-     OS-dependent, do not use this method. (see Time>>asSeconds)"
-
-    ^ (secondsHi * 16r10000) + secondsLow
+    OperatingSystem computeDatePartsOf:secondsLow and:secondsHi for:[
+        :year :month :day | d := day. m := month. y := year.
+    ].
+    OperatingSystem computeTimePartsOf:secondsLow and:secondsHi for:[
+        :hours :minutes :secs | h := hours. min := minutes. s := secs.
+    ].
+    d printOn:aStream.
+    aStream nextPut:$-.
+    m printOn:aStream.
+    aStream nextPut:$-.
+    y printOn:aStream.
+    aStream space.
+    h printOn:aStream leftPaddedTo:2 with:$0. 
+    aStream nextPut:$:.
+    min printOn:aStream leftPaddedTo:2 with:$0.
+    aStream nextPut:$:.
+    s printOn:aStream leftPaddedTo:2 with:$0.
 
     "
-     AbsoluteTime asSeconds
+     AbsoluteTime now 
+     AbsoluteTime fromSeconds:0 
+     Time now            
+     Date today         
     "
 !
 
-asDate
-    "return a Date object from the receiver"
+storeOn:aStream
+    aStream nextPut:$(; 
+            nextPutAll:self class name; 
+            nextPutAll:' new setSecondsLow:'.
+    secondsLow storeOn:aStream.
+    aStream nextPutAll:' and:'.
+    secondsHi storeOn:aStream.
+    aStream nextPut:$).
 
-    ^ Date fromOSTime:(Array with:secondsLow with:secondsHi) 
-!
+    "
+     AbsoluteTime now storeString '(AbsoluteTime new setSecondsLow:39757 and:12087)'
 
-asTime
-    ^ Time fromOSTime:(Array with:secondsLow with:secondsHi)
+     AbsoluteTime readFromString:(AbsoluteTime now storeString) 
+    "
 ! !
 
-!AbsoluteTime methodsFor:'private'!
-
-secondsLow
-    ^ secondsLow
-!
-
-secondsHi
-    ^ secondsHi
-!
-
-getSeconds
-    ^ (secondsHi * 16r10000) + secondsLow
-!
-
-setSeconds:secs
-    secondsHi := secs // 16r10000.
-    secondsLow := secs \\ 16r10000
-!
-
-setSecondsLow:secsLow and:secsHi
-    secondsHi := secsHi.
-    secondsLow := secsLow
-! !
--- a/Unix.st	Wed Feb 08 04:10:51 1995 +0100
+++ b/Unix.st	Wed Feb 08 04:11:17 1995 +0100
@@ -21,7 +21,7 @@
 COPYRIGHT (c) 1988 by Claus Gittinger
 	     All Rights Reserved
 
-$Header: /cvs/stx/stx/libbasic/Attic/Unix.st,v 1.25 1995-02-05 21:34:39 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Attic/Unix.st,v 1.26 1995-02-08 03:11:10 claus Exp $
 '!
 
 !OperatingSystem primitiveDefinitions!
@@ -155,7 +155,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libbasic/Attic/Unix.st,v 1.25 1995-02-05 21:34:39 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Attic/Unix.st,v 1.26 1995-02-08 03:11:10 claus Exp $
 "
 !
 
@@ -2150,7 +2150,7 @@
 .
     aBlock value:low value:hi
 
-    "OperatingSystem getTimeTimeInto:[:low :hi | low printNewline. hi printNewline]"
+    "OperatingSystem getTimeInto:[:low :hi | low printNewline. hi printNewline]"
 !
 
 getTime
@@ -2170,14 +2170,16 @@
 
 computeDatePartsOf:timeParts for:aBlock
     "compute year, month and day from the ostime in timeParts,
-     and evaluate the argument, a 3-arg block with these."
+     and evaluate the argument, a 3-arg block with these.
+     Conversion is to localtime including any daylight saving adjustments."
 
      ^ self computeDatePartsOf:(timeParts at:1) and:(timeParts at:2) for:aBlock
 !
 
 computeTimePartsOf:timeParts for:aBlock
     "compute hour, minute and seconds from the ostime in timeParts,
-     and evaluate the argument, a 3-arg block with these."
+     and evaluate the argument, a 3-arg block with these.
+     Conversion is to localtime including any daylight saving adjustments."
 
      ^ self computeTimePartsOf:(timeParts at:1) and:(timeParts at:2) for:aBlock
 !
@@ -2185,6 +2187,7 @@
 computeDatePartsOf:timeLow and:timeHi for:aBlock
     "compute year, month and day from the time-parts timeLow and
      timeHi and evaluate the argument, a 3-arg block with these.
+     Conversion is to localtime including any daylight saving adjustments.
 
      This method was added to avoid LargeInteger arithmetic and to be
      independent of how the OperatingSystem represents time;
@@ -2213,6 +2216,7 @@
 computeTimePartsOf:timeLow and:timeHi for:aBlock
     "compute hours, minutes and seconds from the time-parts timeLow and
      timeHi and evaluate the argument, a 3-arg block with these.
+     Conversion is to localtime including any daylight saving adjustments.
 
      This method was added to avoid LargeInteger arithmetic and to be
      independent of how the OperatingSystem represents time;
@@ -2240,7 +2244,8 @@
 
 computeTimeAndDateFrom:timeParts
     "given an Array containing the OS-dependent time, return an Array
-     containing year, month, day, hour, minute and seconds"
+     containing year, month, day, hour, minute and seconds.
+     Conversion is to localtime including any daylight saving adjustments."
 
     |low hi year month day hours minutes seconds ret|
 
@@ -2262,8 +2267,7 @@
 	month = _MKSMALLINT(tmPtr->tm_mon + 1);
 	day = _MKSMALLINT(tmPtr->tm_mday);
     }
-%}
-.
+%}.
     year notNil ifTrue:[
 	"I would love to have SELF-like inline objects ..."
 	ret := Array new:6.
@@ -2278,6 +2282,39 @@
     ^ self primitiveFailed
 !
 
+computeTimePartsFromYear:y month:m day:d hour:h minute:min seconds:s
+    "return an Array containing the OS-dependent time for the given
+     time and day. The arguments are assumed to be in localtime including
+     any daylight saving adjustings."
+
+    |low hi|
+
+%{
+    struct tm tm;
+    long t;
+
+    if (_isSmallInteger(y) && _isSmallInteger(m) && _isSmallInteger(d)
+     && _isSmallInteger(h) && _isSmallInteger(min) && _isSmallInteger(s)) {
+	tm.tm_hour = _intVal(h);
+	tm.tm_min = _intVal(min);
+	tm.tm_sec = _intVal(s);
+
+	tm.tm_year = _intVal(y) - 1900;
+	tm.tm_mon = _intVal(m) - 1;
+	tm.tm_mday = _intVal(d);
+	tm.tm_isdst = -1;
+
+	t = mktime(&tm);
+	low = _MKSMALLINT(t & 0xFFFF);
+	hi = _MKSMALLINT((t >> 16) & 0xFFFF);
+    }
+%}.
+    low notNil ifTrue:[
+	^ Array with:low with:hi
+    ].    
+    ^ self primitiveFailed
+!
+
 getMillisecondTime
     "This returns the millisecond timers value. 
      The range is limited to 0..1fffffff (i.e. the SmallInteger range) to avoid
@@ -2703,10 +2740,10 @@
 	argv = (char **) malloc(sizeof(char *) * (nargs + 1));
 	if (argv) {
 	    for (i=0; i < nargs; i++) {
-	        arg = _ArrayInstPtr(argArray)->a_element[i];
-	        if (__isString(arg)) {
+		arg = _ArrayInstPtr(argArray)->a_element[i];
+		if (__isString(arg)) {
 		    argv[i] = (char *) _stringVal(arg);
-	        }
+		}
 	    }
 	    argv[i] = NULL;
 	    execv(_stringVal(aPath), argv);
@@ -3117,8 +3154,8 @@
 	info at:#gid put:gid.
 	info at:#size put:size.
 	info at:#id put:id.
-	info at:#accessTime       put:(Time fromUnixTimeLow:atimeLow and:atimeHi).
-	info at:#modificationTime put:(Time fromUnixTimeLow:mtimeLow and:mtimeHi).
+	info at:#accessTime       put:(AbsoluteTime fromOSTimeLow:atimeLow and:atimeHi).
+	info at:#modificationTime put:(AbsoluteTime fromOSTimeLow:mtimeLow and:mtimeHi).
 	^ info
    ].
    self primitiveFailed
@@ -3263,10 +3300,12 @@
     }
 %}
 .
-    timeLow notNil ifTrue:[^ Time fromUnixTimeLow:timeLow and:timeHi].
+    timeLow notNil ifTrue:[^ AbsoluteTime fromOSTimeLow:timeLow and:timeHi].
     self primitiveFailed
 
-    "OperatingSystem timeOfLastChange:'/'"
+    "
+     OperatingSystem timeOfLastChange:'/'
+    "
 !
 
 timeOfLastAccess:aPathName
@@ -3290,10 +3329,12 @@
     }
 %}
 .
-    timeLow notNil ifTrue:[^ Time fromUnixTimeLow:timeLow and:timeHi].
+    timeLow notNil ifTrue:[^ AbsoluteTime fromOSTimeLow:timeLow and:timeHi].
     self primitiveFailed
 
-    "OperatingSystem timeOfLastAccess:'/'"
+    "
+     OperatingSystem timeOfLastAccess:'/'
+    "
 !
 
 idOf:aPathName