UDBCSQLite3Statement>>at:putDateTime: and DateAndTime>>readFrom:defaultOffset:

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
7 messages Options
Reply | Threaded
Open this post in threaded view
|

UDBCSQLite3Statement>>at:putDateTime: and DateAndTime>>readFrom:defaultOffset:

alistairgrant
Hi All,

UDBCSQLite3Statement>>at:putDateTime: currently writes date and times
using DateAndTime's default print string, i.e.
YYYY-MM-DDTHH:MM:SS.mmmmmm+hh:ss

SQLite3 doesn't support timezones, and expects text formatted date/times
to be:

YYYY-MM-DD HH:MM:SS.mmm

See: https://www.sqlite.org/datatype3.html

The concensus, as far as I can tell, is that UTC times should always be
stored (which seems to be the only sensible option).

Changing UDBCSQLite3Statement>>at:putDateTime: to:

at: aColumn putDateTime: aDateTime
        "Put the supplied DateAndTime in column aColumn.
       
        SQLite3 supports three date/time formats: text, real (Julian day), integer (unix seconds).
        We use the ISO8601 text format: YYYY-MM-DD HH:MM:SS.SSS
        See https://www.sqlite.org/datatype3.html"

        | s |
       
        s := UDBCSQLite3DateTimeString streamContents: [ :stream | |utc |
                utc := aDateTime asDateAndTime asUTC.
                utc printYMDOn: stream.
                stream nextPut: Character space.
                utc printHMSOn: stream.
                stream nextPut: $..
                stream nextPutAll: ((aDateTime nanoSecond / 1000000) rounded printPaddedWith: $0 to: 3) ].
        ^ self library with: handle at: aColumn putString: s


writes date / times in the correct format.

Note that SQLite3 doesn't do much in the way of format checking, so the
old implementation didn't raise an error, but can cause problems if the
database is shared with other applications that follow the rules (which
is why I hit this problem).

To provide some backward compatibility, and follow the rule of being
strict in what you write and forgiving in what you read, we need to
modify UDBCSQLite3Statement>>dateTimeAt: to accept timezones when
supplied, or default to UTC time.

Unfortunately, the current DateAndTime>>readFrom: method assumes the
local timezone if none is specified.

I can think of two approaches to solve this:

1. Modify UDBCSQLite3Statement>>dateTimeAt: to add 'Z' to the string if
no timezone is specified, i.e. make UTC explicit.

2. Extend DateAndTime class to support #readFrom:defaultOffset: so
that UTC can be specified as the default, instead of the local timezone,
and modify UDBCSQLite3Statement>>dateTimeAt: to use UTC as the default.

I prefer the second approach, but realise that this is a change to the
core Pharo classes, so will implement the first if that is the concensus.
I've included the modified methods for the second approach below.

The existing automated tests fail if only #at:putDateTime: is modified,
and succeed if both #at:putDateTime: and #dateTimeAt: are modified.

What do you think?

Thanks!
Alistair


UDBCSQLite3Statement>>dateTimeAt: aColumn
        | utc |
        utc := DateAndTime readFrom: (self library stringFrom: handle at: aColumn) readStream defaultOffset: Duration zero.
        ^utc offset: DateAndTime localOffset.



All methods from DateAndTime class>>


readFrom: aStream defaultOffset: defaultOffset
        "Parse and return a new DateAndTime instance from stream,
        as a Date, an optional Time and an optional TimeZone offset.
        The time defaults to midnight, the timezone to defaultOffset"
        "self readFrom: '2013-03-04T23:47:52.876+01:00' readStream"

        | date time offset |
        date := Date readFrom: aStream.
        [ aStream atEnd or: [ '0123456789Z+-' includes: aStream peek ] ]
                whileFalse: [ aStream next ].
  ('0123456789' includes: aStream peek)
                ifTrue: [ time := Time readFrom: aStream ]
                ifFalse: [ time := Time midnight ].
        aStream skipSeparators.
        offset := self readTimezoneOffsetFrom: aStream default: defaultOffset.
        ^ self
                year: date year
                month: date monthIndex
                day: date dayOfMonth
                hour: time hour
                minute: time minute
                second: time second
                nanoSecond: time nanoSecond
                offset: offset



readFrom: aStream
        "Parse and return a new DateAndTime instance from stream,
        as a Date, an optional Time and an optional TimeZone offset.
        The time defaults to midnight, the timezone to the local offset"
        "self readFrom: '2013-03-04T23:47:52.876+01:00' readStream"

        ^self readFrom: aStream defaultOffset: self localOffset.



readTimezoneOffsetFrom: stream default: defaultOffset
        "Read and return an optional timezone offset in the form of
        [+|-]hh[[separator]mm[[separator]ss]] or Z from stream as a duration.
        If there is no offset, return the defaultOffset."

        | sign hour minute second |
        (stream peekFor: $Z) ifTrue: [ ^ Duration zero ].
        hour := minute := second := 0.
        ^ ('+-' includes: stream peek)
                ifTrue: [
                        sign := stream next = $- ifTrue: [ -1 ] ifFalse: [ 1 ].
                        hour := self readTwoDigitIntegerFrom: stream.
                        (self readOptionalSeparatorFrom: stream)
                                ifNotNil: [
                                        minute := self readTwoDigitIntegerFrom: stream.
                                        (self readOptionalSeparatorFrom: stream)
                                                ifNotNil: [
                                                        second := Integer readFrom: stream ] ].
                        Duration seconds: sign * ((hour * 3600) + (minute * 60) + second) ]
                ifFalse: [ defaultOffset ]



readTimezoneOffsetFrom: stream
        "Read and return an optional timezone offset in the form of
        [+|-]hh[[separator]mm[[separator]ss]] or Z from stream as a duration.
        If there is no offset, return the local offset."

        ^self readTimezoneOffsetFrom: stream default: self localOffset

Reply | Threaded
Open this post in threaded view
|

Re: UDBCSQLite3Statement>>at:putDateTime: and DateAndTime>>readFrom:defaultOffset:

Sven Van Caekenberghe-2

> On 26 Jun 2016, at 14:59, Alistair Grant <[hidden email]> wrote:
>
> Hi All,
>
> UDBCSQLite3Statement>>at:putDateTime: currently writes date and times
> using DateAndTime's default print string, i.e.
> YYYY-MM-DDTHH:MM:SS.mmmmmm+hh:ss
>
> SQLite3 doesn't support timezones, and expects text formatted date/times
> to be:
>
> YYYY-MM-DD HH:MM:SS.mmm
>
> See: https://www.sqlite.org/datatype3.html
>
> The concensus, as far as I can tell, is that UTC times should always be
> stored (which seems to be the only sensible option).
>
> Changing UDBCSQLite3Statement>>at:putDateTime: to:
>
> at: aColumn putDateTime: aDateTime
> "Put the supplied DateAndTime in column aColumn.
>
> SQLite3 supports three date/time formats: text, real (Julian day), integer (unix seconds).
> We use the ISO8601 text format: YYYY-MM-DD HH:MM:SS.SSS
> See https://www.sqlite.org/datatype3.html"
>
> | s |
>
> s := UDBCSQLite3DateTimeString streamContents: [ :stream | |utc |
> utc := aDateTime asDateAndTime asUTC.
> utc printYMDOn: stream.
> stream nextPut: Character space.
> utc printHMSOn: stream.
> stream nextPut: $..
> stream nextPutAll: ((aDateTime nanoSecond / 1000000) rounded printPaddedWith: $0 to: 3) ].
> ^ self library with: handle at: aColumn putString: s
>
>
> writes date / times in the correct format.
>
> Note that SQLite3 doesn't do much in the way of format checking, so the
> old implementation didn't raise an error, but can cause problems if the
> database is shared with other applications that follow the rules (which
> is why I hit this problem).
>
> To provide some backward compatibility, and follow the rule of being
> strict in what you write and forgiving in what you read, we need to
> modify UDBCSQLite3Statement>>dateTimeAt: to accept timezones when
> supplied, or default to UTC time.
>
> Unfortunately, the current DateAndTime>>readFrom: method assumes the
> local timezone if none is specified.
>
> I can think of two approaches to solve this:
>
> 1. Modify UDBCSQLite3Statement>>dateTimeAt: to add 'Z' to the string if
> no timezone is specified, i.e. make UTC explicit.
>
> 2. Extend DateAndTime class to support #readFrom:defaultOffset: so
> that UTC can be specified as the default, instead of the local timezone,
> and modify UDBCSQLite3Statement>>dateTimeAt: to use UTC as the default.
>
> I prefer the second approach, but realise that this is a change to the
> core Pharo classes, so will implement the first if that is the concensus.
> I've included the modified methods for the second approach below.

Yes, option 2 is the right way to go. Your code looks OK from a cursory look.

Please propose a real slice and make certain you add a couple of good unit tests, this is really crucial.

> The existing automated tests fail if only #at:putDateTime: is modified,
> and succeed if both #at:putDateTime: and #dateTimeAt: are modified.
>
> What do you think?
>
> Thanks!
> Alistair
>
>
> UDBCSQLite3Statement>>dateTimeAt: aColumn
> | utc |
> utc := DateAndTime readFrom: (self library stringFrom: handle at: aColumn) readStream defaultOffset: Duration zero.
> ^utc offset: DateAndTime localOffset.
>
>
>
> All methods from DateAndTime class>>
>
>
> readFrom: aStream defaultOffset: defaultOffset
> "Parse and return a new DateAndTime instance from stream,
> as a Date, an optional Time and an optional TimeZone offset.
> The time defaults to midnight, the timezone to defaultOffset"
> "self readFrom: '2013-03-04T23:47:52.876+01:00' readStream"
>
> | date time offset |
> date := Date readFrom: aStream.
> [ aStream atEnd or: [ '0123456789Z+-' includes: aStream peek ] ]
> whileFalse: [ aStream next ].
>   ('0123456789' includes: aStream peek)
> ifTrue: [ time := Time readFrom: aStream ]
> ifFalse: [ time := Time midnight ].
> aStream skipSeparators.
> offset := self readTimezoneOffsetFrom: aStream default: defaultOffset.
> ^ self
> year: date year
> month: date monthIndex
> day: date dayOfMonth
> hour: time hour
> minute: time minute
> second: time second
> nanoSecond: time nanoSecond
> offset: offset
>
>
>
> readFrom: aStream
> "Parse and return a new DateAndTime instance from stream,
> as a Date, an optional Time and an optional TimeZone offset.
> The time defaults to midnight, the timezone to the local offset"
> "self readFrom: '2013-03-04T23:47:52.876+01:00' readStream"
>
> ^self readFrom: aStream defaultOffset: self localOffset.
>
>
>
> readTimezoneOffsetFrom: stream default: defaultOffset
> "Read and return an optional timezone offset in the form of
> [+|-]hh[[separator]mm[[separator]ss]] or Z from stream as a duration.
> If there is no offset, return the defaultOffset."
>
> | sign hour minute second |
> (stream peekFor: $Z) ifTrue: [ ^ Duration zero ].
> hour := minute := second := 0.
> ^ ('+-' includes: stream peek)
> ifTrue: [
> sign := stream next = $- ifTrue: [ -1 ] ifFalse: [ 1 ].
> hour := self readTwoDigitIntegerFrom: stream.
> (self readOptionalSeparatorFrom: stream)
> ifNotNil: [
> minute := self readTwoDigitIntegerFrom: stream.
> (self readOptionalSeparatorFrom: stream)
> ifNotNil: [
> second := Integer readFrom: stream ] ].
> Duration seconds: sign * ((hour * 3600) + (minute * 60) + second) ]
> ifFalse: [ defaultOffset ]
>
>
>
> readTimezoneOffsetFrom: stream
> "Read and return an optional timezone offset in the form of
> [+|-]hh[[separator]mm[[separator]ss]] or Z from stream as a duration.
> If there is no offset, return the local offset."
>
> ^self readTimezoneOffsetFrom: stream default: self localOffset
>


Reply | Threaded
Open this post in threaded view
|

Re: UDBCSQLite3Statement>>at:putDateTime: and DateAndTime>>readFrom:defaultOffset:

alistairgrant
Hi Sven,

On Sun, Jun 26, 2016 at 03:34:15PM +0200, Sven Van Caekenberghe wrote:

>
> > On 26 Jun 2016, at 14:59, Alistair Grant <[hidden email]> wrote:
> >
> > Hi All,
> >
> > UDBCSQLite3Statement>>at:putDateTime: currently writes date and times
> > using DateAndTime's default print string, i.e.
> > YYYY-MM-DDTHH:MM:SS.mmmmmm+hh:ss
> >
> > SQLite3 doesn't support timezones, and expects text formatted date/times
> > to be:
> >
> > YYYY-MM-DD HH:MM:SS.mmm
> >
> > See: https://www.sqlite.org/datatype3.html
> >
> > The concensus, as far as I can tell, is that UTC times should always be
> > stored (which seems to be the only sensible option).
> >
> > Changing UDBCSQLite3Statement>>at:putDateTime: to:
> >
> > at: aColumn putDateTime: aDateTime
> > "Put the supplied DateAndTime in column aColumn.
> >
> > SQLite3 supports three date/time formats: text, real (Julian day), integer (unix seconds).
> > We use the ISO8601 text format: YYYY-MM-DD HH:MM:SS.SSS
> > See https://www.sqlite.org/datatype3.html"
> >
> > | s |
> >
> > s := UDBCSQLite3DateTimeString streamContents: [ :stream | |utc |
> > utc := aDateTime asDateAndTime asUTC.
> > utc printYMDOn: stream.
> > stream nextPut: Character space.
> > utc printHMSOn: stream.
> > stream nextPut: $..
> > stream nextPutAll: ((aDateTime nanoSecond / 1000000) rounded printPaddedWith: $0 to: 3) ].
> > ^ self library with: handle at: aColumn putString: s
> >
> >
> > writes date / times in the correct format.
> >
> > Note that SQLite3 doesn't do much in the way of format checking, so the
> > old implementation didn't raise an error, but can cause problems if the
> > database is shared with other applications that follow the rules (which
> > is why I hit this problem).
> >
> > To provide some backward compatibility, and follow the rule of being
> > strict in what you write and forgiving in what you read, we need to
> > modify UDBCSQLite3Statement>>dateTimeAt: to accept timezones when
> > supplied, or default to UTC time.
> >
> > Unfortunately, the current DateAndTime>>readFrom: method assumes the
> > local timezone if none is specified.
> >
> > I can think of two approaches to solve this:
> >
> > 1. Modify UDBCSQLite3Statement>>dateTimeAt: to add 'Z' to the string if
> > no timezone is specified, i.e. make UTC explicit.
> >
> > 2. Extend DateAndTime class to support #readFrom:defaultOffset: so
> > that UTC can be specified as the default, instead of the local timezone,
> > and modify UDBCSQLite3Statement>>dateTimeAt: to use UTC as the default.
> >
> > I prefer the second approach, but realise that this is a change to the
> > core Pharo classes, so will implement the first if that is the concensus.
> > I've included the modified methods for the second approach below.
>
> Yes, option 2 is the right way to go. Your code looks OK from a cursory look.
>
> Please propose a real slice and make certain you add a couple of good unit tests, this is really crucial.

Thanks for your feedback.

I'll certainly include automated tests in the slice.

I'm still getting up to speed with fogbugz and the patch system.  Should
this be submitted as two separate issues (one for the UDBC package and
one for Kernel-Chronolgy), or as a single issue?

Thanks again,
Alistair


Reply | Threaded
Open this post in threaded view
|

Re: UDBCSQLite3Statement>>at:putDateTime: and DateAndTime>>readFrom:defaultOffset:

Esteban A. Maringolo
As a side note... in all the applications where I use SQLite3, when
storing DateAndTime I use the Unix representation (milliseconds since
epoch) in UTC, although it is unreadable for the end user, it is more
compact, and faster to read/store.

Regards!


Esteban A. Maringolo


2016-06-29 15:43 GMT-03:00 Alistair Grant <[hidden email]>:

> Hi Sven,
>
> On Sun, Jun 26, 2016 at 03:34:15PM +0200, Sven Van Caekenberghe wrote:
>>
>> > On 26 Jun 2016, at 14:59, Alistair Grant <[hidden email]> wrote:
>> >
>> > Hi All,
>> >
>> > UDBCSQLite3Statement>>at:putDateTime: currently writes date and times
>> > using DateAndTime's default print string, i.e.
>> > YYYY-MM-DDTHH:MM:SS.mmmmmm+hh:ss
>> >
>> > SQLite3 doesn't support timezones, and expects text formatted date/times
>> > to be:
>> >
>> > YYYY-MM-DD HH:MM:SS.mmm
>> >
>> > See: https://www.sqlite.org/datatype3.html
>> >
>> > The concensus, as far as I can tell, is that UTC times should always be
>> > stored (which seems to be the only sensible option).
>> >
>> > Changing UDBCSQLite3Statement>>at:putDateTime: to:
>> >
>> > at: aColumn putDateTime: aDateTime
>> >     "Put the supplied DateAndTime in column aColumn.
>> >
>> >     SQLite3 supports three date/time formats: text, real (Julian day), integer (unix seconds).
>> >     We use the ISO8601 text format: YYYY-MM-DD HH:MM:SS.SSS
>> >     See https://www.sqlite.org/datatype3.html"
>> >
>> >     | s |
>> >
>> >     s := UDBCSQLite3DateTimeString streamContents: [ :stream | |utc |
>> >             utc := aDateTime asDateAndTime asUTC.
>> >             utc printYMDOn: stream.
>> >             stream nextPut: Character space.
>> >             utc printHMSOn: stream.
>> >             stream nextPut: $..
>> >             stream nextPutAll: ((aDateTime nanoSecond / 1000000) rounded printPaddedWith: $0 to: 3) ].
>> >     ^ self library with: handle at: aColumn putString: s
>> >
>> >
>> > writes date / times in the correct format.
>> >
>> > Note that SQLite3 doesn't do much in the way of format checking, so the
>> > old implementation didn't raise an error, but can cause problems if the
>> > database is shared with other applications that follow the rules (which
>> > is why I hit this problem).
>> >
>> > To provide some backward compatibility, and follow the rule of being
>> > strict in what you write and forgiving in what you read, we need to
>> > modify UDBCSQLite3Statement>>dateTimeAt: to accept timezones when
>> > supplied, or default to UTC time.
>> >
>> > Unfortunately, the current DateAndTime>>readFrom: method assumes the
>> > local timezone if none is specified.
>> >
>> > I can think of two approaches to solve this:
>> >
>> > 1. Modify UDBCSQLite3Statement>>dateTimeAt: to add 'Z' to the string if
>> > no timezone is specified, i.e. make UTC explicit.
>> >
>> > 2. Extend DateAndTime class to support #readFrom:defaultOffset: so
>> > that UTC can be specified as the default, instead of the local timezone,
>> > and modify UDBCSQLite3Statement>>dateTimeAt: to use UTC as the default.
>> >
>> > I prefer the second approach, but realise that this is a change to the
>> > core Pharo classes, so will implement the first if that is the concensus.
>> > I've included the modified methods for the second approach below.
>>
>> Yes, option 2 is the right way to go. Your code looks OK from a cursory look.
>>
>> Please propose a real slice and make certain you add a couple of good unit tests, this is really crucial.
>
> Thanks for your feedback.
>
> I'll certainly include automated tests in the slice.
>
> I'm still getting up to speed with fogbugz and the patch system.  Should
> this be submitted as two separate issues (one for the UDBC package and
> one for Kernel-Chronolgy), or as a single issue?
>
> Thanks again,
> Alistair
>
>

Reply | Threaded
Open this post in threaded view
|

Re: UDBCSQLite3Statement>>at:putDateTime: and DateAndTime>>readFrom:defaultOffset:

alistairgrant
In reply to this post by alistairgrant
I've finally got this to the point where I think it can be submitted.

The previous version missed a case (sql between).  To keep backward
compatibility with earlier versions of UDBC SQLite3 I've sacrificed a
bit of conformaty and made the representation:

YYYY-MM-DD HH:MM:SS.ssssss

(the difference being microseconds instead of millseconds).  My limited
interoperability testing (Python / Django) suggests this shouldn't be a
problem.

The tricky bit is that it affects four different packages:

1. UDBC-SQLite-Base (UDBCSQLite3Statement, PierceNg.49)
2. Glorp (UDBCSQLite3Platform, AlistairGrant.129)
3. Kernel (DateAndTime, TheIntegrator.2293)
4. Kernel-Tests (DateAndTimeTest, TheIntegrator.65)

I assume that I can create a fogbugz issue and submit a single slice
that will contain the changes to DateAndTime and DateAndTimeTest for
Pharo 6.

What's the best way to submit this for Pharo 5?

The Glorp changes are dependent on the Kernel changes, and the
UDBC-SQLite-Base changes are dependent on the Glorp changes.

I guess that for Glorp, the best way is to include the Kernel changes as
an extension for Pharo 5.

How is a dependency such as that between UDBC-SQLite-Base and Glorp
normally handled?

Thanks!
Alistair


'From Pharo5.0 of 16 April 2015 [Latest update: #50760] on 10 July 2016 at 10:29:14.682983 am'!

!DateAndTime class methodsFor: 'input' stamp: 'AlistairGrant 6/25/2016 22:55'!
readFrom: aStream defaultOffset: defaultOffset
        "Parse and return a new DateAndTime instance from stream,
        as a Date, an optional Time and an optional TimeZone offset.
        The time defaults to midnight, the timezone to defaultOffset"
        "self readFrom: '2013-03-04T23:47:52.876+01:00' readStream"

        | date time offset |
        date := Date readFrom: aStream.
        [ aStream atEnd or: [ '0123456789Z+-' includes: aStream peek ] ]
                whileFalse: [ aStream next ].
  ('0123456789' includes: aStream peek)
                ifTrue: [ time := Time readFrom: aStream ]
                ifFalse: [ time := Time midnight ].
        aStream skipSeparators.
        offset := self readTimezoneOffsetFrom: aStream default: defaultOffset.
        ^ self
                year: date year
                month: date monthIndex
                day: date dayOfMonth
                hour: time hour
                minute: time minute
                second: time second
                nanoSecond: time nanoSecond
                offset: offset! !

!DateAndTime class methodsFor: 'input' stamp: 'AlistairGrant 6/25/2016 22:55'!
readFrom: aStream
        "Parse and return a new DateAndTime instance from stream,
        as a Date, an optional Time and an optional TimeZone offset.
        The time defaults to midnight, the timezone to the local offset"
        "self readFrom: '2013-03-04T23:47:52.876+01:00' readStream"

        ^self readFrom: aStream defaultOffset: self localOffset.! !

!DateAndTime class methodsFor: 'input' stamp: 'AlistairGrant 6/25/2016 22:47'!
readTimezoneOffsetFrom: stream default: defaultOffset
        "Read and return an optional timezone offset in the form of
        [+|-]hh[[separator]mm[[separator]ss]] or Z from stream as a duration.
        If there is no offset, return the defaultOffset."

        | sign hour minute second |
        (stream peekFor: $Z) ifTrue: [ ^ Duration zero ].
        hour := minute := second := 0.
        ^ ('+-' includes: stream peek)
                ifTrue: [
                        sign := stream next = $- ifTrue: [ -1 ] ifFalse: [ 1 ].
                        hour := self readTwoDigitIntegerFrom: stream.
                        (self readOptionalSeparatorFrom: stream)
                                ifNotNil: [
                                        minute := self readTwoDigitIntegerFrom: stream.
                                        (self readOptionalSeparatorFrom: stream)
                                                ifNotNil: [
                                                        second := Integer readFrom: stream ] ].
                        Duration seconds: sign * ((hour * 3600) + (minute * 60) + second) ]
                ifFalse: [ defaultOffset ]! !

!DateAndTime class methodsFor: 'input' stamp: 'AlistairGrant 6/25/2016 22:47'!
readTimezoneOffsetFrom: stream
        "Read and return an optional timezone offset in the form of
        [+|-]hh[[separator]mm[[separator]ss]] or Z from stream as a duration.
        If there is no offset, return the local offset."

        ^self readTimezoneOffsetFrom: stream default: self localOffset! !


!DateAndTimeTest methodsFor: 'tests - offset' stamp: 'AlistairGrant 7/3/2016 21:18'!
testReadFromDefaultOffsetNotSpecified
        "self debug: #testReadFromDefaultOffsetSpecified"

        self assert: (DateAndTime readFrom: '2016-07-03T21:16:16.708241' readStream defaultOffset: Duration zero) offset printString equals: '0:00:00:00'.
! !

!DateAndTimeTest methodsFor: 'tests - offset' stamp: 'AlistairGrant 7/3/2016 21:17'!
testReadFromDefaultOffsetSpecified
        "self debug: #testReadFromDefaultOffsetSpecified"

        self assert: (DateAndTime readFrom: '2016-07-03T21:16:16.708241+02:00' readStream defaultOffset: Duration zero) offset printString equals: '0:02:00:00'.
! !



'From Pharo5.0 of 16 April 2015 [Latest update: #50760] on 10 July 2016 at 10:29:18.333218 am'!

!UDBCSQLite3Platform methodsFor: 'conversion-times' stamp: 'AlistairGrant 7/3/2016 09:33'!
toTimestamp: anObject for: aType
        "From DatabasePlatform."

        anObject isNil ifTrue: [^nil].
        anObject class = Dialect timestampClass ifTrue: [^anObject asUTC].
        anObject isInteger ifTrue: [^anObject].
        ^anObject asDateAndTime asUTC! !

!UDBCSQLite3Platform methodsFor: 'conversion-times' stamp: 'AlistairGrant 7/3/2016 19:32'!
printTimestamp: aTimestamp on: stream for: aType

        aTimestamp isNil ifTrue: [stream nextPutAll: 'NULL'. ^self].
        stream
                nextPut: $';
                nextPutAll: (self class datetimeToString: aTimestamp);
                nextPut: $'.! !


!UDBCSQLite3Platform class methodsFor: 'conversion' stamp: 'AlistairGrant 7/3/2016 19:30'!
datetimeToString: aDateAndTime
        "Convert the supplied DateAndTime to something close to SQLite3's text timestamp format:
       
        YYYY-MM-DD HH:MM:SS.ssssss
       
        To keep backward compatibility with previous versions, microseconds are supplied instead of milliseconds (what SQLite3 officially supports).  Most other applications seem to handle this OK."
        | string |
       
        aDateAndTime class = Dialect timestampClass ifFalse: [ ^aDateAndTime ].
        string := UDBCSQLite3DateTimeString
                streamContents: [ :stream |
                        | utc n len |
                        utc := aDateAndTime asDateAndTime asUTC.
                        utc printYMDOn: stream.
                        stream nextPut: Character space.
                        utc printHMSOn: stream.
                        n := utc nanoSecond.
                        n ~= 0
                                ifTrue: [ len := 9.
                                        [ n \\ 10 = 0 ]
                                                whileTrue: [ n := n / 10.
                                                        len := len - 1 ].
                                        stream nextPut: $..
                                        n
                                                printOn: stream
                                                base: 10
                                                length: len
                                                padded: true ] ].
        ^string! !


!UDBCSQLite3Statement methodsFor: 'public - accessing' stamp: 'AlistairGrant 7/2/2016 22:54'!
dateTimeAt: aColumn
        | utc |
        utc := DateAndTime
                readFrom: (self library stringFrom: handle at: aColumn) readStream
                defaultOffset: Duration zero.
        ^ utc offset: DateAndTime localOffset! !

!UDBCSQLite3Statement methodsFor: 'public - accessing' stamp: 'AlistairGrant 7/3/2016 19:42'!
at: aColumn putDateTime: aDateTime
        "Put the supplied DateAndTime in column aColumn.

    SQLite3 supports three date/time formats: text, real (Julian day), integer (unix seconds).
    We use the ISO8601 text format: YYYY-MM-DD HH:MM:SS.SSS
    See https://www.sqlite.org/datatype3.html"

        | s |
        s := UDBCSQLite3Platform datetimeToString: aDateTime asDateAndTime.
        ^ self library with: handle at: aColumn putString: s! !

Reply | Threaded
Open this post in threaded view
|

Re: UDBCSQLite3Statement>>at:putDateTime: and DateAndTime>>readFrom:defaultOffset:

Sven Van Caekenberghe-2
Hi,

Regarding the DateAndTime change.

> On 11 Jul 2016, at 07:52, Alistair Grant <[hidden email]> wrote:
>
> I've finally got this to the point where I think it can be submitted.
>
> The previous version missed a case (sql between).  To keep backward
> compatibility with earlier versions of UDBC SQLite3 I've sacrificed a
> bit of conformaty and made the representation:
>
> YYYY-MM-DD HH:MM:SS.ssssss
>
> (the difference being microseconds instead of millseconds).  My limited
> interoperability testing (Python / Django) suggests this shouldn't be a
> problem.
>
> The tricky bit is that it affects four different packages:
>
> 1. UDBC-SQLite-Base (UDBCSQLite3Statement, PierceNg.49)
> 2. Glorp (UDBCSQLite3Platform, AlistairGrant.129)
> 3. Kernel (DateAndTime, TheIntegrator.2293)
> 4. Kernel-Tests (DateAndTimeTest, TheIntegrator.65)
>
> I assume that I can create a fogbugz issue and submit a single slice
> that will contain the changes to DateAndTime and DateAndTimeTest for
> Pharo 6.

Yes, please create a slice. But first for Pharo 6, then back port to 5.

I assume that your change is adding the default timezone parameter ?

A small remark: in your unit tests, don't compare string output, but objects. In the 1st test, compare to Duration zero, in the second to 2 hours.

Sven

> What's the best way to submit this for Pharo 5?
>
> The Glorp changes are dependent on the Kernel changes, and the
> UDBC-SQLite-Base changes are dependent on the Glorp changes.
>
> I guess that for Glorp, the best way is to include the Kernel changes as
> an extension for Pharo 5.
>
> How is a dependency such as that between UDBC-SQLite-Base and Glorp
> normally handled?
>
> Thanks!
> Alistair
>
>
> 'From Pharo5.0 of 16 April 2015 [Latest update: #50760] on 10 July 2016 at 10:29:14.682983 am'!
>
> !DateAndTime class methodsFor: 'input' stamp: 'AlistairGrant 6/25/2016 22:55'!
> readFrom: aStream defaultOffset: defaultOffset
> "Parse and return a new DateAndTime instance from stream,
> as a Date, an optional Time and an optional TimeZone offset.
> The time defaults to midnight, the timezone to defaultOffset"
> "self readFrom: '2013-03-04T23:47:52.876+01:00' readStream"
>
> | date time offset |
> date := Date readFrom: aStream.
> [ aStream atEnd or: [ '0123456789Z+-' includes: aStream peek ] ]
> whileFalse: [ aStream next ].
>   ('0123456789' includes: aStream peek)
> ifTrue: [ time := Time readFrom: aStream ]
> ifFalse: [ time := Time midnight ].
> aStream skipSeparators.
> offset := self readTimezoneOffsetFrom: aStream default: defaultOffset.
> ^ self
> year: date year
> month: date monthIndex
> day: date dayOfMonth
> hour: time hour
> minute: time minute
> second: time second
> nanoSecond: time nanoSecond
> offset: offset! !
>
> !DateAndTime class methodsFor: 'input' stamp: 'AlistairGrant 6/25/2016 22:55'!
> readFrom: aStream
> "Parse and return a new DateAndTime instance from stream,
> as a Date, an optional Time and an optional TimeZone offset.
> The time defaults to midnight, the timezone to the local offset"
> "self readFrom: '2013-03-04T23:47:52.876+01:00' readStream"
>
> ^self readFrom: aStream defaultOffset: self localOffset.! !
>
> !DateAndTime class methodsFor: 'input' stamp: 'AlistairGrant 6/25/2016 22:47'!
> readTimezoneOffsetFrom: stream default: defaultOffset
> "Read and return an optional timezone offset in the form of
> [+|-]hh[[separator]mm[[separator]ss]] or Z from stream as a duration.
> If there is no offset, return the defaultOffset."
>
> | sign hour minute second |
> (stream peekFor: $Z) ifTrue: [ ^ Duration zero ].
> hour := minute := second := 0.
> ^ ('+-' includes: stream peek)
> ifTrue: [
> sign := stream next = $- ifTrue: [ -1 ] ifFalse: [ 1 ].
> hour := self readTwoDigitIntegerFrom: stream.
> (self readOptionalSeparatorFrom: stream)
> ifNotNil: [
> minute := self readTwoDigitIntegerFrom: stream.
> (self readOptionalSeparatorFrom: stream)
> ifNotNil: [
> second := Integer readFrom: stream ] ].
> Duration seconds: sign * ((hour * 3600) + (minute * 60) + second) ]
> ifFalse: [ defaultOffset ]! !
>
> !DateAndTime class methodsFor: 'input' stamp: 'AlistairGrant 6/25/2016 22:47'!
> readTimezoneOffsetFrom: stream
> "Read and return an optional timezone offset in the form of
> [+|-]hh[[separator]mm[[separator]ss]] or Z from stream as a duration.
> If there is no offset, return the local offset."
>
> ^self readTimezoneOffsetFrom: stream default: self localOffset! !
>
>
> !DateAndTimeTest methodsFor: 'tests - offset' stamp: 'AlistairGrant 7/3/2016 21:18'!
> testReadFromDefaultOffsetNotSpecified
> "self debug: #testReadFromDefaultOffsetSpecified"
>
> self assert: (DateAndTime readFrom: '2016-07-03T21:16:16.708241' readStream defaultOffset: Duration zero) offset printString equals: '0:00:00:00'.
> ! !
>
> !DateAndTimeTest methodsFor: 'tests - offset' stamp: 'AlistairGrant 7/3/2016 21:17'!
> testReadFromDefaultOffsetSpecified
> "self debug: #testReadFromDefaultOffsetSpecified"
>
> self assert: (DateAndTime readFrom: '2016-07-03T21:16:16.708241+02:00' readStream defaultOffset: Duration zero) offset printString equals: '0:02:00:00'.
> ! !
>
>
>
> 'From Pharo5.0 of 16 April 2015 [Latest update: #50760] on 10 July 2016 at 10:29:18.333218 am'!
>
> !UDBCSQLite3Platform methodsFor: 'conversion-times' stamp: 'AlistairGrant 7/3/2016 09:33'!
> toTimestamp: anObject for: aType
> "From DatabasePlatform."
>
> anObject isNil ifTrue: [^nil].
> anObject class = Dialect timestampClass ifTrue: [^anObject asUTC].
> anObject isInteger ifTrue: [^anObject].
> ^anObject asDateAndTime asUTC! !
>
> !UDBCSQLite3Platform methodsFor: 'conversion-times' stamp: 'AlistairGrant 7/3/2016 19:32'!
> printTimestamp: aTimestamp on: stream for: aType
>
> aTimestamp isNil ifTrue: [stream nextPutAll: 'NULL'. ^self].
> stream
> nextPut: $';
> nextPutAll: (self class datetimeToString: aTimestamp);
> nextPut: $'.! !
>
>
> !UDBCSQLite3Platform class methodsFor: 'conversion' stamp: 'AlistairGrant 7/3/2016 19:30'!
> datetimeToString: aDateAndTime
> "Convert the supplied DateAndTime to something close to SQLite3's text timestamp format:
>
> YYYY-MM-DD HH:MM:SS.ssssss
>
> To keep backward compatibility with previous versions, microseconds are supplied instead of milliseconds (what SQLite3 officially supports).  Most other applications seem to handle this OK."
> | string |
>
> aDateAndTime class = Dialect timestampClass ifFalse: [ ^aDateAndTime ].
> string := UDBCSQLite3DateTimeString
> streamContents: [ :stream |
> | utc n len |
> utc := aDateAndTime asDateAndTime asUTC.
> utc printYMDOn: stream.
> stream nextPut: Character space.
> utc printHMSOn: stream.
> n := utc nanoSecond.
> n ~= 0
> ifTrue: [ len := 9.
> [ n \\ 10 = 0 ]
> whileTrue: [ n := n / 10.
> len := len - 1 ].
> stream nextPut: $..
> n
> printOn: stream
> base: 10
> length: len
> padded: true ] ].
> ^string! !
>
>
> !UDBCSQLite3Statement methodsFor: 'public - accessing' stamp: 'AlistairGrant 7/2/2016 22:54'!
> dateTimeAt: aColumn
> | utc |
> utc := DateAndTime
> readFrom: (self library stringFrom: handle at: aColumn) readStream
> defaultOffset: Duration zero.
> ^ utc offset: DateAndTime localOffset! !
>
> !UDBCSQLite3Statement methodsFor: 'public - accessing' stamp: 'AlistairGrant 7/3/2016 19:42'!
> at: aColumn putDateTime: aDateTime
> "Put the supplied DateAndTime in column aColumn.
>
>    SQLite3 supports three date/time formats: text, real (Julian day), integer (unix seconds).
>    We use the ISO8601 text format: YYYY-MM-DD HH:MM:SS.SSS
>    See https://www.sqlite.org/datatype3.html"
>
> | s |
> s := UDBCSQLite3Platform datetimeToString: aDateTime asDateAndTime.
> ^ self library with: handle at: aColumn putString: s! !
>


Reply | Threaded
Open this post in threaded view
|

Re: UDBCSQLite3Statement>>at:putDateTime: and DateAndTime>>readFrom:defaultOffset:

alistairgrant
Hi Sven,

Thanks for your feedback.

On Mon, Jul 11, 2016 at 08:33:56AM +0200, Sven Van Caekenberghe wrote:

> Hi,
>
> Regarding the DateAndTime change.
>
> > On 11 Jul 2016, at 07:52, Alistair Grant <[hidden email]> wrote:
> >
> > I've finally got this to the point where I think it can be submitted.
> >
> > The previous version missed a case (sql between).  To keep backward
> > compatibility with earlier versions of UDBC SQLite3 I've sacrificed a
> > bit of conformaty and made the representation:
> >
> > YYYY-MM-DD HH:MM:SS.ssssss
> >
> > (the difference being microseconds instead of millseconds).  My limited
> > interoperability testing (Python / Django) suggests this shouldn't be a
> > problem.
> >
> > The tricky bit is that it affects four different packages:
> >
> > 1. UDBC-SQLite-Base (UDBCSQLite3Statement, PierceNg.49)
> > 2. Glorp (UDBCSQLite3Platform, AlistairGrant.129)
> > 3. Kernel (DateAndTime, TheIntegrator.2293)
> > 4. Kernel-Tests (DateAndTimeTest, TheIntegrator.65)
> >
> > I assume that I can create a fogbugz issue and submit a single slice
> > that will contain the changes to DateAndTime and DateAndTimeTest for
> > Pharo 6.
>
> Yes, please create a slice. But first for Pharo 6, then back port to 5.

Shall do.


> I assume that your change is adding the default timezone parameter ?

Yep, so that applications can have a default timezone (offset) of UTC.


> A small remark: in your unit tests, don't compare string output, but
> objects. In the 1st test, compare to Duration zero, in the second to 2
> hours.

Done.


> Sven
>
> > What's the best way to submit this for Pharo 5?
> >
> > The Glorp changes are dependent on the Kernel changes, and the
> > UDBC-SQLite-Base changes are dependent on the Glorp changes.
> >
> > I guess that for Glorp, the best way is to include the Kernel changes as
> > an extension for Pharo 5.
> >
> > How is a dependency such as that between UDBC-SQLite-Base and Glorp
> > normally handled?

I've finally realised the obvious, that making UDBC-SQLite-Base
dependent on Glorp, is a bad idea since not everyone using UDBC will
have Glorp, so I'll reverse the dependency, since the UDBC driver has to
be present for Glorp to use it :-).

Thanks again,
Alistair