[squeak-dev] The Inbox: Chronology-Core-dtl.56.mcz

David T. Lewis lewis at mail.msen.com
Sat Sep 5 01:04:08 UTC 2020


Hi Levente,

On Sat, Sep 05, 2020 at 12:01:21AM +0200, Levente Uzonyi wrote:
> Hi Dave,
> 
> I skimmed through the diff and my impression was that the goal of these 
> changes was to remove the ChronologyConstants shared pool.
> What's the motivation to do that? Does Cuis not have shared pools?

I can't speak for Juan, but my assumption is that the original motivation
was that of Cuis overall - make things as simple and approachable as
possible.

My personal motivation in suggesting it for Squeak is that I'm interested
in making the Squeak UTC DateAndTime available for Cuis, which is actually
a rather challenging thing to do. It's easier for me if I don't have to
re-implement Juan's improvments after (hypothetically) porting the code
from Squeak to Cuis. So if they are worthwhile changes, and I think that
they are, then it's easier to just do the update once in Squeak so that
we can just be rid of the incompatibilities.

> 
> And the criticism:
> 1) Variable references are replaced with message sends. Even of those are 
> quick sends, they'll still be slightly slower than using the variables 
> (with the current VMs).

As far as I can tell, this has no practical impact, except for the #oneDay
case that you identified. But I don't think that it is actually a problem,
see below.

> 2) Some replacement methods are not quick and create new objects. For 
> example, OneDay, a single Duration of one day is replaced with #oneDay, a 
> method returning the expression 1 day. Each invocation of the method 
> creates a new object.
> In my image, there are 19821 Date instances. If all of those had their own 
> custom one day long Duration objects, which is a side effect of these 
> changes in the long run, my image would be ~620 kiB larger (64-bit image, 
> object header + 2 variables => 32 bytes each).
> There's a solution: cache the shared instance in a variable. :)

If it is a problem, then this is an error on my part (not Juan's). After
adopting the main part of the Cuis changes, #oneDay was one of a couple
of remaining cases that I addressed with trivial replacements.

But there are no senders of #oneDay in the image other than a unit test.
So I think that it is not likely to be an issue.

Dave


> 3) A new role for the Time class: provide the variables 
> ChronologyConstants used to. I think Time is already overloaded with 
> roles; it doesn't need a new one. Even if the shared pool goes away, there 
> should be a separate class holding these constants. For example, we could 
> call it ChronologyConstants. :)
> 

I would not be in favor of that :-)

Thanks very much for reviewing.

Dave


> 
> Levente
> 
> On Fri, 4 Sep 2020, David T. Lewis wrote:
> 
> >I have been looking at Chronology in Cuis, as I would like to be able to
> >contribute Squeak's UTC style DateAndTime for consideration in Cuis.
> >
> >Juan has done some cleanups that simplify Chronology by getting rid of
> >an unnecessary shared pool for constants. I think this is a good 
> >improvement
> >so I put it in the inbox here for review.
> >
> >To me this seems cleaner and simpler. All tests still pass of course.
> >
> >Dave
> >
> >
> >On Fri, Sep 04, 2020 at 02:54:38PM +0000, commits at source.squeak.org wrote:
> >>A new version of Chronology-Core was added to project The Inbox:
> >>http://source.squeak.org/inbox/Chronology-Core-dtl.56.mcz
> >>
> >>==================== Summary ====================
> >>
> >>Name: Chronology-Core-dtl.56
> >>Author: dtl
> >>Time: 4 September 2020, 10:54:37.509663 am
> >>UUID: a33e5fab-940e-41ed-b05c-76f8ff54f5ee
> >>Ancestors: Chronology-Core-ul.55
> >>
> >>Adopt simplifications from Cuis. Remove ChronologyConstants. Retain jmv 
> >>author initials where possible. The shared pool is not required, it is 
> >>simpler to use methods in the responsible classes.
> >>
> >>=============== Diff against Chronology-Core-ul.55 ===============
> >>
> >>Item was removed:
> >>- SharedPool subclass: #ChronologyConstants
> >>- 	instanceVariableNames: ''
> >>- 	classVariableNames: 'DayNames DaysInMonth MicrosecondsInDay 
> >>MonthNames NanosInMillisecond NanosInSecond OneDay SecondsInDay 
> >>SecondsInHour SecondsInMinute SqueakEpoch Zero'
> >>- 	poolDictionaries: ''
> >>- 	category: 'Chronology-Core'!
> >>- 
> >>- !ChronologyConstants commentStamp: 'brp 3/12/2004 14:34' prior: 0!
> >>- ChronologyConstants is a SharedPool for the constants used by the 
> >>Kernel-Chronology classes.!
> >>
> >>Item was removed:
> >>- ----- Method: ChronologyConstants class>>initialize (in category 'class 
> >>initialization') -----
> >>- initialize
> >>- 	"ChronologyConstants initialize" 
> >>- 
> >>- 	SqueakEpoch := 2415386. 		"Julian day number of 1 Jan 
> >>1901" - 	SecondsInDay := 86400.
> >>- 	SecondsInHour := 3600.
> >>- 	SecondsInMinute := 60.
> >>- 	MicrosecondsInDay := 24 * 60 * 60 * 1000000.
> >>- 	NanosInSecond := 10 raisedTo: 9.
> >>- 	NanosInMillisecond := 10 raisedTo: 6.
> >>- 	DayNames := #(Sunday Monday Tuesday Wednesday Thursday Friday 
> >>Saturday).
> >>- 
> >>- 	MonthNames := #(	January February March April May June
> >>- 						July August September 
> >>October November December).
> >>- 	DaysInMonth := #(31 28 31 30 31 30 31 31 30 31 30 31)!
> >>
> >>Item was changed:
> >>  Timespan subclass: #Date
> >>  	instanceVariableNames: ''
> >>  	classVariableNames: ''
> >>+ 	poolDictionaries: ''
> >>- 	poolDictionaries: 'ChronologyConstants'
> >>  	category: 'Chronology-Core'!
> >>
> >>  !Date commentStamp: 'cmm 6/28/2016 21:36' prior: 0!
> >>  Instances of Date are Timespans with duration of 1 day.  As with all 
> >>  Chronology Timespan sub-instances, Dates can be instantiated as 
> >>  position values which compare equally to any other instance of the same 
> >>  Date, irregardless of the timezone in which either is created.
> >>
> >>  However, like the other Timespan subInstances, there are rare cases 
> >>  where it may be desirable to use instances of Date to represent a 
> >>  particular 1-day span of time at a particular locality on the globe.  
> >>  All Timespans, including Dates, may specify a particular timezone 
> >>  offset for this purpose.!
> >>
> >>Item was changed:
> >>  ----- Method: Date class>>fromDays: (in category 'smalltalk-80') -----
> >>  fromDays: dayCount
> >>  	"Days since 1 January 1901"
> >>
> >>+ 	^ self julianDayNumber: dayCount + Time squeakEpoch!
> >>- 	^ self julianDayNumber: dayCount + SqueakEpoch!
> >>
> >>Item was changed:
> >>  ----- Method: Date class>>starting: (in category 'squeak protocol') 
> >>  -----
> >>  starting: aDateAndTime
> >>  	^ self
> >>  		starting: aDateAndTime midnight
> >>+ 		duration: 1 day!
> >>- 		duration: Duration oneDay!
> >>
> >>Item was changed:
> >>  Magnitude subclass: #DateAndTime
> >>  	instanceVariableNames: 'utcMicroseconds localOffsetSeconds'
> >>  	classVariableNames: 'AutomaticTimezone ClockProvider 
> >>  	InitializeFromPrimitive LocalTimeZone PosixEpochJulianDays'
> >>+ 	poolDictionaries: ''
> >>- 	poolDictionaries: 'ChronologyConstants'
> >>  	category: 'Chronology-Core'!
> >>
> >>  !DateAndTime commentStamp: 'dtl 3/12/2016 10:32' prior: 0!
> >>  I represent a point in UTC time as defined by ISO 8601. I have zero 
> >>  duration.
> >>
> >>  My implementation uses variables utcMicroseconds and 
> >>  localOffsetSeconds. This represents time magnitude as elapsed 
> >>  microseconds since the Posix epoch, with localOffsetSeconds 
> >>  representing local offset from UTC. The magnitude is used for 
> >>  comparison and duration calculations, and the local offset is used for 
> >>  displaying this magnitude in the context of a local time zone.
> >>
> >>  The implementation ignores leap seconds, which are adjustments made to 
> >>  maintain earth rotational clock time in synchronization with elapsed 
> >>  seconds.
> >>
> >>  DateAndTime class>>now will use #primitiveUtcWithOffset to obtain 
> >>  current time in UTC microseconds with current local offset in seconds. 
> >>  The primitive provides an atomic query for UTC time and local offset as 
> >>  measured by the OS platform.  If primitiveUtcWithOffset is not 
> >>  available, the traditional implementation is used, which relies on a 
> >>  primitive for microseconds in the local time zone and derives UTC based 
> >>  on the TimeZone setting.
> >>  !
> >>
> >>Item was changed:
> >>  ----- Method: DateAndTime class>>epochOffset (in category 'private') 
> >>  -----
> >>  epochOffset
> >>  	"Elaspsed seconds from the Smalltalk epoch to the Posix epoch"
> >>+ 	^self daysFromSmalltalkEpochToPosixEpoch * Time secondsInDay!
> >>- 	^self daysFromSmalltalkEpochToPosixEpoch * SecondsInDay!
> >>
> >>Item was changed:
> >>  ----- Method: DateAndTime>>posixEpochJulianDays (in category 
> >>  'initialize-release') -----
> >>  posixEpochJulianDays
> >>
> >>+ 	^self class daysFromSmalltalkEpochToPosixEpoch + Time squeakEpoch!
> >>- 	^self class daysFromSmalltalkEpochToPosixEpoch + SqueakEpoch!
> >>
> >>Item was changed:
> >>  ----- Method: DateAndTime>>ticks:offset: (in category 'private') -----
> >>  ticks: ticks offset: utcOffset
> >>  	"ticks is {julianDayNumber. secondCount. nanoSeconds}"
> >>
> >>  	| jdn s nanos normalizedTicks |
> >>  	normalizedTicks := ticks copy.
> >>+ 	self normalize: 3 ticks: normalizedTicks base: Time nanosInSecond.
> >>+ 	self normalize: 2 ticks: normalizedTicks base: Time secondsInDay.
> >>- 	self normalize: 3 ticks: normalizedTicks base: NanosInSecond.
> >>- 	self normalize: 2 ticks: normalizedTicks base: SecondsInDay.
> >>
> >>  	jdn	:= normalizedTicks at: 1.
> >>  	s := normalizedTicks at: 2.
> >>  	nanos := normalizedTicks at: 3.
> >>  	localOffsetSeconds := utcOffset ifNil: [0] ifNotNil: [utcOffset 
> >>  	asSeconds].
> >>  	utcMicroseconds := self microsecondsFromDay: jdn seconds: s nanos: 
> >>  	nanos offset: localOffsetSeconds.
> >>  !
> >>
> >>Item was changed:
> >>  Magnitude subclass: #Duration
> >>  	instanceVariableNames: 'nanos seconds'
> >>  	classVariableNames: ''
> >>+ 	poolDictionaries: ''
> >>- 	poolDictionaries: 'ChronologyConstants'
> >>  	category: 'Chronology-Core'!
> >>
> >>  !Duration commentStamp: 'dtl 7/11/2009 15:03' prior: 0!
> >>  I represent a duration of time. I have nanosecond precision!
> >>
> >>Item was changed:
> >>  ----- Method: Duration class>>days: (in category 'squeak protocol') 
> >>  -----
> >>  days: aNumber
> >>
> >>+ 	^ self seconds: aNumber * Time secondsInDay nanoSeconds: 0!
> >>- 	^ self seconds: aNumber * SecondsInDay nanoSeconds: 0!
> >>
> >>Item was changed:
> >>  ----- Method: Duration class>>days:hours:minutes:seconds:nanoSeconds: 
> >>  (in category 'squeak protocol') -----
> >>  days: days hours: hours minutes: minutes seconds: seconds nanoSeconds: 
> >>  nanos
> >>
> >>   	^self
> >>  		seconds: seconds
> >>+ 			+ (minutes * Time secondsInMinute) 
> >>+ 			+ (hours * Time secondsInHour)
> >>+ 			+ (days * Time secondsInDay)
> >>- 			+ (minutes * SecondsInMinute) 
> >>- 			+ (hours * SecondsInHour)
> >>- 			+ (days * SecondsInDay)
> >>  		nanoSeconds: nanos
> >>  !
> >>
> >>Item was changed:
> >>  ----- Method: Duration class>>days:seconds: (in category 'ansi 
> >>  protocol') -----
> >>  days: days seconds: seconds
> >>
> >>+ 	^ self basicNew seconds: days * Time secondsInDay + seconds 
> >>nanoSeconds: 0!
> >>- 	^ self basicNew seconds: days * SecondsInDay + seconds nanoSeconds: 0
> >>- !
> >>
> >>Item was changed:
> >>  ----- Method: Duration class>>hours: (in category 'squeak protocol') 
> >>  -----
> >>  hours: aNumber
> >>
> >>+ 	^ self seconds: aNumber * Time secondsInHour nanoSeconds: 0!
> >>- 	^ self seconds: aNumber * SecondsInHour nanoSeconds: 0!
> >>
> >>Item was removed:
> >>- ----- Method: Duration class>>initialize (in category 
> >>'initialize-release') -----
> >>- initialize
> >>- 	ChronologyConstants classPool
> >>- 		at: #Zero
> >>- 		put:
> >>- 			(self basicNew
> >>- 				seconds: 0
> >>- 				nanoSeconds: 0) ;
> >>- 		at: #OneDay
> >>- 		put: 1 day!
> >>
> >>Item was changed:
> >>  ----- Method: Duration class>>milliSeconds: (in category 'squeak 
> >>  protocol') -----
> >>  milliSeconds: milliCount
> >>
> >>  	^self
> >>  		seconds: (milliCount quo: 1000)
> >>+ 		nanoSeconds: (milliCount rem: 1000) * 1000000!
> >>- 		nanoSeconds: (milliCount rem: 1000) * NanosInMillisecond!
> >>
> >>Item was changed:
> >>  ----- Method: Duration class>>minutes: (in category 'squeak protocol') 
> >>  -----
> >>  minutes: aNumber
> >>
> >>+ 	^ self seconds: aNumber * Time secondsInMinute nanoSeconds: 0!
> >>- 	^ self seconds: aNumber * SecondsInMinute nanoSeconds: 0!
> >>
> >>Item was changed:
> >>  ----- Method: Duration class>>nanoSeconds: (in category 'squeak 
> >>  protocol') -----
> >>  nanoSeconds: nanos
> >>  	"This method is slow. If you have nanos less than 10^6 you should 
> >>  	use #seconds:nanoSeconds: instead."
> >>
> >>  	| quo |
> >>+ 	quo _ nanos quo: Time nanosInSecond.
> >>- 	quo := nanos quo: NanosInSecond.
> >>  	^ self basicNew
> >>  		seconds: quo
> >>+ 		nanoSeconds: nanos - (quo * Time nanosInSecond)!
> >>- 		nanoSeconds: nanos - (quo * NanosInSecond)
> >>- !
> >>
> >>Item was changed:
> >>  ----- Method: Duration class>>oneDay (in category 'squeak protocol') 
> >>  -----
> >>  oneDay
> >>  	"Answer the canonicalized Duration representing length of 1 day.  
> >>  	Used by Dates."
> >>+ 	^ 1 day!
> >>- 	^ OneDay!
> >>
> >>Item was changed:
> >>  ----- Method: Duration class>>seconds:nanoSeconds: (in category 'squeak 
> >>  protocol') -----
> >>  seconds: seconds nanoSeconds: nanos
> >>
> >>  	^ self basicNew
> >>  		seconds: seconds truncated
> >>+ 		nanoSeconds: seconds fractionPart * Time nanosInSecond + 
> >>nanos!
> >>- 		nanoSeconds: seconds fractionPart * NanosInSecond + nanos!
> >>
> >>Item was changed:
> >>  ----- Method: Duration class>>zero (in category 'ansi protocol') -----
> >>  zero
> >>+ 
> >>+ 	^ self basicNew seconds: 0 nanoSeconds: 0
> >>+ !
> >>- 	"Answer the canonicalized instance of Duration zero."
> >>- 	^ Zero!
> >>
> >>Item was changed:
> >>  ----- Method: Duration>>asNanoSeconds (in category 'squeak protocol') 
> >>  -----
> >>  asNanoSeconds
> >>
> >>+ 	^seconds * Time nanosInSecond + nanos!
> >>- 	^seconds * NanosInSecond + nanos!
> >>
> >>Item was changed:
> >>  ----- Method: Duration>>days (in category 'ansi protocol') -----
> >>  days
> >>  	"Answer the number of days the receiver represents."
> >>
> >>+ 	^ seconds quo: Time secondsInDay!
> >>- 	^ seconds quo: SecondsInDay
> >>- !
> >>
> >>Item was changed:
> >>  ----- Method: Duration>>hours (in category 'ansi protocol') -----
> >>  hours
> >>  	"Answer the number of hours the receiver represents."
> >>
> >>
> >>+ 	^ (seconds rem: Time secondsInDay) quo: Time secondsInHour!
> >>- 	^ (seconds rem: SecondsInDay) quo: SecondsInHour!
> >>
> >>Item was changed:
> >>  ----- Method: Duration>>minutes (in category 'ansi protocol') -----
> >>  minutes
> >>-
> >>  	"Answer the number of minutes the receiver represents."
> >>
> >>+ 	^ (seconds rem: Time secondsInHour) quo: Time secondsInMinute!
> >>- 
> >>- 	^ (seconds rem: SecondsInHour) quo: SecondsInMinute!
> >>
> >>Item was changed:
> >>  ----- Method: Duration>>seconds (in category 'ansi protocol') -----
> >>  seconds
> >>  	"Answer the number of seconds the receiver represents."
> >>
> >>+ 	^seconds rem: Time secondsInMinute!
> >>- 	^seconds rem: SecondsInMinute!
> >>
> >>Item was changed:
> >>  ----- Method: Duration>>seconds:nanoSeconds: (in category 'private') 
> >>  -----
> >>  seconds: secondCount nanoSeconds: nanoCount
> >>  	"Private - only used by Duration class"
> >>
> >>  	seconds := secondCount.
> >>  	nanos := nanoCount rounded.
> >>  	"normalize if signs do not match"
> >>  	[ nanos < 0 and: [ seconds > 0 ] ]
> >>  		whileTrue: [ seconds := seconds - 1.
> >>+ 			nanos := nanos + Time nanosInSecond ].
> >>- 			nanos := nanos + NanosInSecond ].
> >>  	[ seconds < 0 and: [ nanos > 0 ] ]
> >>  		whileTrue: [ seconds := seconds + 1.
> >>+ 			nanos := nanos - Time nanosInSecond ]
> >>- 			nanos := nanos - NanosInSecond ]
> >>
> >>  !
> >>
> >>Item was changed:
> >>  ----- Method: Duration>>ticks (in category 'private') -----
> >>  ticks
> >>  	"Answer an array {days. seconds. nanoSeconds}. Used by DateAndTime 
> >>  	and Time."
> >>
> >>  	| days |
> >>  	days := self days.
> >>  	^ Array
> >>  		with: days
> >>+ 		with: seconds - (days * Time secondsInDay)
> >>- 		with: seconds - (days * SecondsInDay)
> >>  		with: nanos
> >>  !
> >>
> >>Item was changed:
> >>  Timespan subclass: #Month
> >>  	instanceVariableNames: ''
> >>  	classVariableNames: ''
> >>+ 	poolDictionaries: ''
> >>- 	poolDictionaries: 'ChronologyConstants'
> >>  	category: 'Chronology-Core'!
> >>
> >>  !Month commentStamp: 'cbr 7/28/2010 18:11' prior: 0!
> >>  I represent a month.
> >>
> >>  For example, to get the number of days this month, you can evaluate the 
> >>  following expression:
> >>
> >>  Month current daysInMonth!
> >>
> >>Item was added:
> >>+ ----- Method: Month class>>daysInMonth (in category 'inquiries') -----
> >>+ daysInMonth
> >>+ 	^#(31 28 31 30 31 30 31 31 30 31 30 31)!
> >>
> >>Item was changed:
> >>  ----- Method: Month class>>daysInMonth:forYear: (in category 
> >>  'smalltalk-80') -----
> >>  daysInMonth: indexOrName forYear: yearInteger
> >>
> >>  	| index |
> >>  	index := indexOrName isInteger
> >>  				ifTrue: [indexOrName]
> >>  				ifFalse: [self indexOfMonth: indexOrName].
> >>+ 	^ (self daysInMonth at: index)
> >>- 	^ (DaysInMonth at: index)
> >>  			+ ((index = 2
> >>  					and: [Year isLeapYear: yearInteger])
> >>  						ifTrue: [1] ifFalse: [0])
> >>  !
> >>
> >>Item was changed:
> >>  ----- Method: Month class>>indexOfMonth: (in category 'smalltalk-80') 
> >>  -----
> >>  indexOfMonth: aMonthName
> >>
> >>
> >>+ 	1 to: 12 do: [ :i |  (aMonthName, '*' match: (self monthNames at: 
> >>i)) ifTrue: [^i] ].
> >>+ 	self error: aMonthName , ' is not a recognized month name'!
> >>- 	1 to: 12 do: [ :i |  (aMonthName, '*' match: (MonthNames at: i)) 
> >>ifTrue: [^i] ].
> >>- 	self error: aMonthName , ' is not a recognized month name'.!
> >>
> >>Item was added:
> >>+ ----- Method: Month class>>monthNames (in category 'inquiries') -----
> >>+ monthNames
> >>+ 	^#(January February March April May June July August September 
> >>October November December)!
> >>
> >>Item was changed:
> >>  ----- Method: Month class>>nameOfMonth: (in category 'smalltalk-80') 
> >>  -----
> >>  nameOfMonth: anIndex
> >>
> >>+ 	^ self monthNames at: anIndex!
> >>- 	^ MonthNames at: anIndex.!
> >>
> >>Item was changed:
> >>  Magnitude subclass: #Time
> >>  	instanceVariableNames: 'seconds nanos'
> >>  	classVariableNames: 'ClockPolicy HighResClockTicksPerMillisecond 
> >>  	LastClockTick UpdateVMTimeZoneCacheAt UseHighResClockForTiming'
> >>+ 	poolDictionaries: ''
> >>- 	poolDictionaries: 'ChronologyConstants'
> >>  	category: 'Chronology-Core'!
> >>
> >>  !Time commentStamp: 'dew 10/23/2004 17:58' prior: 0!
> >>  This represents a particular point in time during any given day.  For 
> >>  example, '5:19:45 pm'.
> >>
> >>  If you need a point in time on a particular day, use DateAndTime.  If 
> >>  you need a duration of time, use Duration.
> >>  !
> >>
> >>Item was changed:
> >>  ----- Method: Time class>>fromSeconds: (in category 'smalltalk-80') 
> >>  -----
> >>  fromSeconds: secondCount
> >>  	"Answer an instance of me that is secondCount number of seconds 
> >>  	since midnight."
> >>
> >>  	| integerSeconds nanos |
> >>  	integerSeconds := secondCount truncated.
> >>  	integerSeconds = secondCount
> >>  		ifTrue: [nanos := 0]
> >>+ 		ifFalse: [nanos := (secondCount - integerSeconds * self 
> >>nanosInSecond) asInteger].
> >>- 		ifFalse: [nanos := (secondCount - integerSeconds * 
> >>NanosInSecond) asInteger].
> >>  	^ self seconds: integerSeconds nanoSeconds: nanos
> >>  !
> >>
> >>Item was changed:
> >>  ----- Method: Time class>>hour:minute:second:nanoSecond: (in category 
> >>  'squeak protocol') -----
> >>+ hour: hour minute: minute second: second nanoSecond: nanoCount
> >>+ 	"Answer a Time"
> >>- hour: hour minute: minute second: second  nanoSecond: nanoCount
> >>- 	"Answer a Time - only second precision for now"
> >>
> >>  	^ self 
> >>+ 		seconds: (hour * self secondsInHour) + (minute * self 
> >>secondsInMinute) + second + 		nanoSeconds: nanoCount!
> >>- 		seconds: (hour * SecondsInHour) + (minute * SecondsInMinute) 
> >>+ second - 		nanoSeconds: nanoCount
> >>- !
> >>
> >>Item was added:
> >>+ ----- Method: Time class>>nanosInSecond (in category 'constants') -----
> >>+ nanosInSecond
> >>+ 	^ 1000000000!
> >>
> >>Item was changed:
> >>  ----- Method: Time class>>noon (in category 'squeak protocol') -----
> >>  noon
> >>
> >>+ 	^ self seconds: self secondsInDay / 2!
> >>- 	^ self seconds: (SecondsInDay / 2)
> >>- !
> >>
> >>Item was changed:
> >>  ----- Method: Time class>>now (in category 'ansi protocol') -----
> >>  now
> >>  	"Answer a Time representing the time right now - this is a 24 hour 
> >>  	clock."
> >>  	| localUsecs localUsecsToday |
> >>  	localUsecs := self localMicrosecondClock.
> >>+ 	localUsecsToday := localUsecs \\ 86400000000. "24 * 60 * 60 * 
> >>1000000"
> >>- 	localUsecsToday := localUsecs \\ MicrosecondsInDay.
> >>  	^ self
> >>  		seconds: localUsecsToday // 1000000
> >>  		nanoSeconds: localUsecsToday \\ 1000000 * 1000!
> >>
> >>Item was added:
> >>+ ----- Method: Time class>>secondsInDay (in category 'constants') -----
> >>+ secondsInDay
> >>+ 	^86400!
> >>
> >>Item was added:
> >>+ ----- Method: Time class>>secondsInHour (in category 'constants') -----
> >>+ secondsInHour
> >>+ 	^3600!
> >>
> >>Item was added:
> >>+ ----- Method: Time class>>secondsInMinute (in category 'constants') 
> >>-----
> >>+ secondsInMinute
> >>+ 	^60!
> >>
> >>Item was added:
> >>+ ----- Method: Time class>>squeakEpoch (in category 'constants') -----
> >>+ squeakEpoch
> >>+ 	^ 2415386. 		"Julian day number of 1 Jan 1901"!
> >>
> >>Item was changed:
> >>  ----- Method: Time>>print24:showSeconds:showSubseconds:on: (in category 
> >>  'printing') -----
> >>  print24: hr24 showSeconds: showSeconds showSubseconds: showSubseconds 
> >>  on: aStream
> >>  	"Format is 'hh:mm:ss' or 'h:mm:ss am'  or, if showSeconds is false, 
> >>  	'hh:mm' or 'h:mm am'.
> >>  	If showSubseconds is true and our nanoSeconds are not zero, a 
> >>  	decimal point and subseconds are added"
> >>
> >>  	| h m s |
> >>  	h := self hour. m := self minute. s := self second.
> >>  	hr24
> >>  		ifTrue:
> >>  			[ h < 10 ifTrue: [ aStream nextPutAll: '0' ].
> >>  			h printOn: aStream ]
> >>  		ifFalse:
> >>  			[ h > 12
> >>  				ifTrue: [h - 12 printOn: aStream]
> >>  				ifFalse:
> >>  					[h < 1
> >>  						ifTrue: [ 12 printOn: 
> >>  						aStream ]
> >>  						ifFalse: [ h printOn: 
> >>  						aStream ]]].
> >>
> >>  	aStream nextPutAll: (m < 10 ifTrue: [':0'] ifFalse: [':']).
> >>  	m printOn: aStream.
> >>
> >>  	showSeconds ifTrue:
> >>  		[ aStream nextPutAll: (s < 10 ifTrue: [':0'] ifFalse: [':']).
> >>  		(showSubseconds not or: [self nanoSecond = 0])
> >>  			ifTrue: [s asInteger printOn: aStream]
> >>+ 			ifFalse: [s asInteger * Time nanosInSecond + self 
> >>nanoSecond asInteger + 				printOn: aStream 
> >>asFixedPoint: Time nanosInSecond]].
> >>- 			ifFalse: [s asInteger * NanosInSecond + self 
> >>nanoSecond asInteger - 				printOn: aStream 
> >>asFixedPoint: NanosInSecond]].
> >>
> >>  	hr24 ifFalse:
> >>  		[ aStream nextPutAll: (h < 12 ifTrue: [' am'] ifFalse: [' 
> >>  		pm']) ].
> >>  !
> >>
> >>Item was changed:
> >>  Object subclass: #TimeZone
> >>  	instanceVariableNames: 'offset abbreviation name'
> >>  	classVariableNames: ''
> >>+ 	poolDictionaries: ''
> >>- 	poolDictionaries: 'ChronologyConstants'
> >>  	category: 'Chronology-Core'!
> >>
> >>  !TimeZone commentStamp: 'dtl 7/11/2009 15:03' prior: 0!
> >>  TimeZone is a simple class to colect the information identifying a UTC 
> >>  time zone.
> >>
> >>  offset			-	Duration	- the time zone's 
> >>  offset from UTC
> >>  abbreviation	-	String		- the abbreviated name for 
> >>  the time zone.
> >>  name			-	String		- the name of the 
> >>  time zone.
> >>
> >>  TimeZone class >> #timeZones returns an array of the known time zones
> >>  TimeZone class >> #default returns the default time zone (Grenwich Mean 
> >>  Time)
> >>  !
> >>
> >>Item was changed:
> >>  Timespan subclass: #Week
> >>  	instanceVariableNames: ''
> >>  	classVariableNames: 'StartDay'
> >>+ 	poolDictionaries: ''
> >>- 	poolDictionaries: 'ChronologyConstants'
> >>  	category: 'Chronology-Core'!
> >>
> >>  !Week commentStamp: 'cbr 7/28/2010 18:11' prior: 0!
> >>  I represent a week.
> >>
> >>  To find out what days of the week on which Squeak is fun, select the 
> >>  following expression, and print it:
> >>
> >>  Week dayNames!
> >>
> >>Item was changed:
> >>+ ----- Method: Week class>>dayNames (in category 'inquiries') -----
> >>- ----- Method: Week class>>dayNames (in category 'squeak protocol') -----
> >>  dayNames
> >>
> >>+ 	^ #(Sunday Monday Tuesday Wednesday Thursday Friday Saturday)!
> >>- 	^ DayNames!
> >>
> >>Item was changed:
> >>  ----- Method: Week class>>indexOfDay: (in category 'squeak protocol') 
> >>  -----
> >>  indexOfDay: aSymbol
> >>
> >>+ 	^ self dayNames indexOf: aSymbol!
> >>- 	^ DayNames indexOf: aSymbol!
> >>
> >>Item was changed:
> >>  ----- Method: Week class>>nameOfDay: (in category 'smalltalk-80') -----
> >>  nameOfDay: anIndex
> >>
> >>+ 	^ self dayNames at: anIndex!
> >>- 	^ DayNames at: anIndex!
> >>
> >>Item was changed:
> >>  ----- Method: Week class>>startDay (in category 'squeak protocol') -----
> >>  startDay
> >>
> >>  	^ StartDay ifNil: [ StartDay
> >>+  := self dayNames first ]
> >>-  := DayNames first ]
> >>  !
> >>
> >>Item was changed:
> >>  ----- Method: Week class>>startDay: (in category 'squeak protocol') 
> >>  -----
> >>  startDay: aSymbol
> >>
> >>+ 	(self dayNames includes: aSymbol)
> >>- 	(DayNames includes: aSymbol)
> >>  		ifTrue: [ StartDay := aSymbol ]
> >>  		ifFalse: [ self error: aSymbol, ' is not a recognised day 
> >>  		name' ]!
> >>
> >>Item was changed:
> >>  ----- Method: Week class>>starting:duration: (in category 'squeak 
> >>  protocol') -----
> >>  starting: aDateAndTime duration: aDuration
> >>  	"Override - the duration is always one week.
> >>  	 Week will start from the Week class>>startDay"
> >>
> >>  	| midnight delta adjusted |
> >>  	midnight := aDateAndTime asDateAndTime midnight.
> >>+ 	delta := ((midnight dayOfWeek + 7 - (self dayNames indexOf: self 
> >>startDay)) rem: 7) abs.
> >>- 	delta := ((midnight dayOfWeek + 7 - (DayNames indexOf: self 
> >>startDay)) rem: 7) abs.
> >>  	adjusted := midnight - (Duration days: delta seconds: 0).
> >>
> >>  	^ super starting: adjusted duration: (Duration weeks: 1)!
> >>
> >>
> 


More information about the Squeak-dev mailing list