On Tue, May 03, 2011 at 04:02:04AM +0200, Levente Uzonyi wrote:
> 
> On Mon, 2 May 2011, David T. Lewis wrote:
> >
> >I have not looked at this carefully, but I suspect an issue in Chronology
> >(as opposed to a VM or primitive issue). DateAndTime initializes some 
> >cached
> >values at image startup time, and thereafter calculates things based on the
> >millisecond clock. If the millisecond clock drifts with respect to system 
> >time
> >on the underlying platform (as presumably would be the case if the system 
> >clock
> >is synchronized using ntp), then DateAndTime's opinion about current time 
> >will
> >drift with respect to the underlying platform.
> 
> The amount of the drift seems to be 1 millisecond every 14-16 seconds on 
> my pc. I wrote some code to get the system time via FFI[1], then ran the 
> following:
> 
> | data |
> data := (1 to: 100) collect: [ :run |
>       1 seconds asDelay wait.
>       { DateAndTime now. Win32SystemTime localDateAndTime } ].
> (data collect: [ :each | each first - each second ] as: Set) sorted explore
> 
> 
> Levente
> 
> [1] http://leves.web.elte.hu/squeak/Win32SystemTime.st

I am now running a similar test (attached) on Linux. I was expecting
to see clock drift exactly the same as that reported on Windows, but
so far after about 15 minutes I see no obvious signs of drift. I
cannot explain this but I'll leave it running for a while and see
if anything interesting happens.

Dave

sample output:

=== Started at 2011-05-03T20:24:35.03-04:00 ===
Test duration 0:00:15:46.01
OS time now: 2011-05-03T20:40:21.039466-04:00
Squeak time now: 2011-05-03T20:40:21.04-04:00
Difference: 0:00:00:00.000534
Drift: 0:00:00:00.000075
=== Started at 2011-05-03T20:24:35.03-04:00 ===
Test duration 0:00:15:49.072
OS time now: 2011-05-03T20:40:24.101675-04:00
Squeak time now: 2011-05-03T20:40:24.102-04:00
Difference: 0:00:00:00.000325
Drift: -0:00:00:00.000134
=== Started at 2011-05-03T20:24:35.03-04:00 ===
Test duration 0:00:15:52.102
OS time now: 2011-05-03T20:40:27.131382-04:00
Squeak time now: 2011-05-03T20:40:27.132-04:00
Difference: 0:00:00:00.000618
Drift: 0:00:00:00.000159
=== Started at 2011-05-03T20:24:35.03-04:00 ===
Test duration 0:00:15:55.136
OS time now: 2011-05-03T20:40:30.165711-04:00
Squeak time now: 2011-05-03T20:40:30.166-04:00
Difference: 0:00:00:00.000289
Drift: -0:00:00:00.00017

'From Squeak4.2 of 3 May 2011 [latest update: #11376] on 3 May 2011 at 8:25:17 
pm'!
Object subclass: #CheckTimeDrift
        instanceVariableNames: ''
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Junk'!
!CheckTimeDrift commentStamp: 'dtl 5/3/2011 20:13' prior: 0!
A CheckTimeDrift is a test for Squeak DateAndTime now versus the underlying 
platform time.

Prerequisites:
- Install TimeZoneDatabase from SqueakSource and set local time zone
- Run under an interpreter VM that provides #primitiveUtcWithOffset

Open a transcript, then doIt:

        [CheckTimeDrift run] fork inspect

!
]style[(221 22 34 25 10),c000000126,,c000126126,!


"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

CheckTimeDrift class
        instanceVariableNames: ''!

!CheckTimeDrift class methodsFor: 'running' stamp: 'dtl 5/3/2011 20:24'!
run
        "Load package TimeZoneDatabase. Set time zone. Run under an
        interpreter VM. Open transcript, then run."

        "[CheckTimeDrift run] fork"
        
        | start diff osTime squeakTime initialDifference drift |
        start := DateAndTime now.
        osTime := CheckTimeDrift now.
        squeakTime := DateAndTime now.
        initialDifference := squeakTime - osTime.

        [osTime := CheckTimeDrift now.
        squeakTime := DateAndTime now.
        diff := squeakTime - osTime.
        drift := diff - initialDifference.
        Transcript cr; nextPutAll: '=== Started at ', start printString, ' ==='.
        Transcript cr; nextPutAll: 'Test duration ', (squeakTime - start) 
printString.
        Transcript cr; nextPutAll: 'OS time now: ', osTime printString.
        Transcript cr; nextPutAll: 'Squeak time now: ', squeakTime printString.
        Transcript cr; nextPutAll: 'Difference: ', diff printString.
        Transcript cr; show: 'Drift: ', drift printString.
        (Delay forSeconds: 3) wait.
        ] repeat! !


!CheckTimeDrift class methodsFor: 'time' stamp: 'dtl 5/3/2011 19:59'!
now

        "self now"

        | uSec pt |
        uSec := self primUtcWithOffset first.
        pt := PointInTime fromPosixSeconds: uSec / 1000000.
        ^ pt asDateAndTime! !


!CheckTimeDrift class methodsFor: 'primitive access' stamp: 'dtl 5/3/2011 
19:54'!
primUtcWithOffset
        "Answer an array with UTC microseconds since the Posix epoch and
        the current seconds offset from GMT in the local time zone.
        This is a named (not numbered) primitive in the null module (ie the VM)"
        
        "self primUtcWithOffset"
        
        <primitive: #primitiveUtcWithOffset>
        self error: 'use an interpreter VM, not Cog'! !

Reply via email to