Thanks Sven. We let the repo as global read because we usually receive
unintentional commits.
Do you think it is worth it to have a kind of DBXTalkInbox ?

Alan, do you think this is useful also for Glorp trunk ?

Thanks!

On Tue, Nov 8, 2011 at 5:59 AM, Sven Van Caekenberghe <s...@beta9.be> wrote:

> Hi,
>
> I have a patch for Glorp(DBX) PostgreSQL to support the newer bytea hex
> format (see
> file:///usr/local/pgsql/share/doc/html/datatype-binary.html#AEN5037). I
> can't write to the repository, so here it is:
>
> PostgreSQLPlatform>>#convertSQLStringToByteArray: aString for: aType
>        aString isNil ifTrue: [ ^ nil ].
>        ^ (aString beginsWith: '\x')
>                ifTrue: [ self convertHexSQLStringToByteArray: aString ]
>                ifFalse: [ self convertEscapeSQLStringToByteArray: aString ]
>
> PostgreSQLPlatform>>#convertEscapeSQLStringToByteArray: aString
>        | aStream str |
>        aStream := (ByteArray new: aString size // 4) writeStream.
>        str := aString readStream.
>        [str atEnd] whileFalse: [ |nextChar|
>                nextChar := str next.
>                aStream nextPut: (nextChar = $\
>                                                                ifTrue:
> [str peek = $\
>
>              ifTrue: [str next asInteger]
>
>              ifFalse: [Number readFrom: (str next: 3) base: 8]]
>                                                                ifFalse:
> [nextChar asInteger])
>        ].
>        aStream close.
>        ^aStream contents
>
> PostgreSQLPlatform>>#convertHexSQLStringToByteArray: aString
>        ^ ByteArray
>                new: (aString size // 2) - 1
>                streamContents: [ :out | | in |
>                        (in := aString readStream) skip: 2.
>                        [ in atEnd ] whileFalse: [
>                                out nextPut: (Number readFrom: (in next: 2)
> base: 16) ] ]
>
> #convertEscapeSQLStringToByteArray: is the old code, unmodified;
> #convertHexSQLStringToByteArray: is new.
> This might be of use upstream as well, I don't really know.
>
> If it would help, I could save this as an MC package somewhere.
>
> Regards,
>
> Sven
>
>
>


-- 
Mariano
http://marianopeck.wordpress.com

Reply via email to