[Seaside] 3.9 and encoding

Martial Boniou Martial.Boniou at ifrance.com
Wed Feb 28 11:51:29 UTC 2007


Hi,

I tought I had 'corrupted' 3.9 images but it seems to be a general issue
for 3.9. I had made the hack as Philippe said. Actually I changed the
Dialect class>>basicIsSqueak test so that it pass well during
installation (to get the SmalltalkImage things and not Smalltalk); I
added a Dialect class>>basicIsSqueak39 (true for SystemVersion number >
7010); I subclass SqueakDatabaseAccessor to Squeak39DatabaseAccessor to
modify the instance method #basicExecuteSQLString to say:

result := connection execute: (aString asWideString convertToEncoding:
'utf-8').

It works well. I did it to test Ramon Leon's Seaside Blog but I didn't
post this because I wasn't sure it was a common problem and because of
the ugliness of the string conversion.

I attach my two mods.

--
Martial

Philippe Marschall a écrit :
| 2007/2/28, Norbert Hartl <norbert at hartl.name>:
| >On Wed, 2007-02-28 at 00:26 +0100, Philippe Marschall wrote:
| >> 2007/2/28, Norbert Hartl <norbert at hartl.name>:
| >> > Hi,
| >> >
| >> > I ran into a encoding problem. I'm using seaside together
| >> > with Glorp. For the web server I use WAKomEncoded39.
| >> > WAKomEncoded39 converts the output to the browser to utf-8.
| >> > But on incoming requests the url escaped characters are
| >> > translated to something different. For me it appears to
| >> > be latin-1 but I've no glue why it should be that way.
| >> > I detected it because my postgresql session has client
| >> > encoding utf-8 turned on and I get an error trying to
| >> > store strings containing characters like ö.
| >>
| >> If you run WAKomEncoded39 on Squeak 3.9 you will have strings with
| >> (new) Squeak encoding in your image which is basically non-unified
| >> unicode. For latin-1 characters this will be indistinguishable from
| >> latin-1. If your database is utf-8 you need to encode your strings to
| >> utf-8 when writing them to your database and decode your strings from
| >> utf-8 when reading from the database (only to convert it back to utf-8
| >> when generating html). You can configure the PostgreS database driver
| >> to do this automatically for you.
| >>
| >Oh, this seems quite easy. But I didn't found anything to configure
| >in the Postgres driver. Do you have any hint?
| 
| PGConnection >> class #buildDefaultFieldConverters
| TestPGConnection >> #testFieldConverter
| 
| You need to register a field converter for your string types that does
| #convertFromEncoding: #utf8
| 
| Sorry that does only do the decoding and not the encoding. I guess in
| your case Glorp does the encoding. I don't know how you can customize
| the Sql generation there but it everything else fails you can change
| PGConnection >> #execute (yes, this is a hack)
| 
| sql := sqlString.
| to
| sql := sqlString convertToEncoding: #utf8.
| 
| Philippe
| 
| P.S.:
| PGConnection >> class #buildDefaultFieldConverters
| has given us a lot of pain because Squeak doesn't have full block closures
| 
| >Norbert
| >
| >_______________________________________________
| >Seaside mailing list
| >Seaside at lists.squeakfoundation.org
| >http://lists.squeakfoundation.org/cgi-bin/mailman/listinfo/seaside
| >

| _______________________________________________
| Seaside mailing list
| Seaside at lists.squeakfoundation.org
| http://lists.squeakfoundation.org/cgi-bin/mailman/listinfo/seaside

-------------- next part --------------
'From Squeak3.10alpha.7068 of 2 February 2007 [latest update: #7068] on 28 February 2007 at 12:48:24 pm'!
Object subclass: #Dialect
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Glorp-Misc'!

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

Dialect class
	instanceVariableNames: 'dialectName timestampClass identitySetClass lookedUpNames'!

!Dialect class methodsFor: 'dates' stamp: ' 5/6/05 12:11'!
addSeconds: seconds to: aTime

	self isVisualWorks ifTrue: [^ aTime addSeconds: seconds].
	self isDolphin ifTrue: [^ self addTimeForDolphin: aTime seconds: seconds].
	self isGNU ifTrue: [^ aTime addSeconds: seconds].
	self isVisualAge ifTrue: [^Time fromSeconds: aTime asSeconds + seconds].
	self error: 'not implemented'.
	^ self! !

!Dialect class methodsFor: 'dates' stamp: ' 5/6/05 12:11'!
addTimeForDolphin: aTime seconds: seconds

	"Dolphin's time/date arithmetic is pretty weak, especially for timestamps. Hack around it. This is likely only to work for seconds <24 hours"

	| result |

	^ aTime class == Time
		ifTrue: [Time fromMilliseconds: (aTime asMilliseconds + (seconds * 1000)) \\ 86400000.]
		ifFalse: [
			result := self timestampClass date: aTime date
				time: (self addTimeForDolphin: aTime time seconds: seconds).
			(seconds > 0 and: [result time < aTime time.])
				ifTrue: [result date: (result date addDays: 1).].
			(seconds < 0 and: [result time > aTime time.])
				ifTrue: [result date: (result date addDays: -1).].
			^ result
		]! !

!Dialect class methodsFor: 'dates' stamp: ' 5/6/05 12:11'!
newTimeWithHours: hours minutes: minutes seconds: seconds milliseconds: milliseconds

	self isGNU ifTrue: [^ Time fromSeconds: hours * 60 * 60 + (minutes * 60) + seconds].
	(self isVisualWorks or: [self isSqueak]) ifTrue: [^ Time fromSeconds: hours * 60 * 60 + (minutes * 60) + seconds].
	self isVisualAge
		ifTrue: [
			^ Time fromMilliseconds: ((hours * 60 * 60) + (minutes * 60) + seconds) * 1000 + milliseconds
		].
	self isObjectStudio ifTrue: [^Time hour: hours minute: minutes second: seconds millisecond: milliseconds].
	self error: 'Not implemented yet'.
	^ self! !

!Dialect class methodsFor: 'dates' stamp: ' 5/6/05 12:11'!
newTimestampWithYears: years
	months: months
	days: days
	hours: hours
	minutes: minutes
	seconds: seconds
	milliseconds: millis
	offset: offset

	| date time ts |

	self isGNU
		ifTrue: [
			^ self timestampClass year: years
				month: months
				day: days
				hour: hours
				minute: minutes
				second: seconds
				offset: ((Dialect smalltalkAt: #Duration) fromSeconds: offset)
		].
	date := self newDateWithYears: years months: months days: days.
	time := self newTimeWithHours: hours minutes: minutes seconds: seconds milliseconds: millis.
	self isVisualWorks
		ifTrue: [^ (self timestampClass fromDate: date andTime: time) addMilliseconds: millis].
	self isSqueak
		ifTrue: [ts := self timestampClass date: date time: time.
			ts time addSeconds: (millis / 1000) asInteger.
				^ts]. 
	self isVisualAge
		ifTrue: [
			^ ((Dialect smalltalkAt: #AbtTimestamp) date: date time: time)
				milliSeconds: millis;
				yourself
		].
	self isObjectStudio ifTrue: [^self timestampClass newDate: date time: time].
	self error: 'not implemented'.
	^ self! !

!Dialect class methodsFor: 'dates' stamp: ' 5/6/05 12:11'!
supportsMillisecondsInTimeStamps

	self isGNU ifTrue: [^ false].
	self isVisualWorks ifTrue: [^ true].
	self isDolphin ifTrue: [^ true].
	self isVisualAge ifTrue: [^ true].
	self isObjectStudio ifTrue: [^true].
	self error: 'not yet implemented'.
	^ self! !

!Dialect class methodsFor: 'dates' stamp: ' 5/6/05 12:11'!
supportsMillisecondsInTimes

	self isGNU ifTrue: [^ false].
	self isVisualWorks ifTrue: [^ false].
	self isSqueak ifTrue: [^false].
	self isDolphin ifTrue: [^ true].
	self isVisualAge ifTrue: [^ true].
	self isObjectStudio ifTrue: [^true]. "Sort of. Supports hundredths of a second"
	^ self! !

!Dialect class methodsFor: 'dates' stamp: ' 5/6/05 12:11'!
timeOffsetFromGMT

	self isGNU ifTrue: [Time timezoneBias / (60 * 60).].
	self isVisualWorks ifTrue: [^ (self smalltalkAt: #TimeZone) default secondsFromGMT / (60 * 60)].
	^ 0! !

!Dialect class methodsFor: 'dates' stamp: ' 5/6/05 12:11'!
timestampClass

	timestampClass == nil ifFalse: [^ timestampClass].
	Dialect isGNU ifTrue: [^ timestampClass := self smalltalkAt: #DateTime].
	(Dialect isSqueak or: [Dialect isDolphin.])
		ifTrue: [^ timestampClass := self smalltalkAt: #TimeStamp].
	Dialect isVisualWorks ifTrue: [^ timestampClass := self smalltalkAt: #Timestamp].
	Dialect isVisualAge ifTrue: [^ timestampClass := self smalltalkAt: #Timestamp].
	Dialect isObjectStudio ifTrue: [^timestampClass := self smalltalkAt: #Timestamp].
	self error: 'Not yet implemented'.
	^ self! !

!Dialect class methodsFor: 'dates' stamp: ' 5/6/05 12:11'!
timestampNow

	Dialect isGNU ifTrue: [^ self timestampClass dateAndTimeNow].
	Dialect isSqueak ifTrue: [^ self timestampClass current].
	Dialect isVisualWorks ifTrue: [^ self timestampClass now].
	Dialect isDolphin ifTrue: [^ self timestampClass current].
	Dialect isVisualAge ifTrue: [^ self timestampClass now].
	Dialect isObjectStudio ifTrue: [^self timestampClass now].
	self error: 'Not yet implemented'.
	^ self! !

!Dialect class methodsFor: 'dates' stamp: ' 5/6/05 12:11'!
timestampNowUTC

	Dialect isGNU ifTrue: [^ self timestampClass utcDateAndTimeNow].
	Dialect isVisualWorks ifTrue: [^ (self smalltalkAt: #Timestamp) fromSeconds: Time secondClock].
	Dialect isDolphin ifTrue: [self error: 'not supported'.].
	self error: 'Not yet implemented'.
	^ self! !

!Dialect class methodsFor: 'dates' stamp: ' 5/6/05 12:11'!
totalSeconds

	self isGNU ifTrue: [^ Time utcSecondClock].
	self isVisualAge ifTrue: [^ (self smalltalkAt: #AbtTimestamp) now totalSeconds].
	^ Time totalSeconds! !


!Dialect class methodsFor: 'private' stamp: ' 5/6/05 12:11'!
basicIsDolphin
	^Smalltalk includesKey: #DolphinSplash.! !

!Dialect class methodsFor: 'private' stamp: ' 5/6/05 12:11'!
basicIsGNU
	^Smalltalk includesKey: #BindingDictionary.! !

!Dialect class methodsFor: 'private' stamp: ' 5/6/05 12:11'!
basicIsObjectStudio
	^Smalltalk class name == #SmalltalkClass.! !

!Dialect class methodsFor: 'private' stamp: 'mhb 2/9/2007 15:24'!
basicIsSqueak
	"tested on Squeak 3.9/3.10 images"
	| squeakVersion |
	squeakVersion := Bag with: Smalltalk.
	Smalltalk
		at: #SmalltalkImage
		ifPresent: [:ea | squeakVersion add: ea current].
	^ squeakVersion
		contains: [:ea | (ea respondsTo: #vmVersion)
				and: [(ea vmVersion copyFrom: 1 to: 6)
						= 'Squeak']]! !

!Dialect class methodsFor: 'private' stamp: 'mhb 2/9/2007 17:04'!
basicIsSqueak39
	"true if 3.9 or more!!"
	^ self basicIsSqueak
		and: [(Smalltalk
				at: #SystemVersion
				ifPresent: [:el | (el current respondsTo: #version)
						and: [(el current version last: 4) asNumber >= 7011]])
				ifNil: [false]]! !

!Dialect class methodsFor: 'private' stamp: ' 5/6/05 12:11'!
basicIsVisualAge

	^ Smalltalk class name == #EsSmalltalkNamespace
	"	| sys |
	sys := Smalltalk at: #System ifAbsent: [^false].
	(sys respondsTo: #vmType) ifFalse: [^false].
	^sys vmType = 'ES'"! !

!Dialect class methodsFor: 'private' stamp: ' 5/6/05 12:11'!
basicIsVisualWorks

	^ Smalltalk class name == #NameSpace
	"Smalltalk class selectors do: [ :s | 
		(s == #versionName and: [ (Smalltalk versionName copyFrom: 1 to: 11) = 'VisualWorks']) 
		    ifTrue: [^true]].
	^false"! !

!Dialect class methodsFor: 'private' stamp: ' 5/6/05 12:11'!
determineDialect

	self basicIsDolphin ifTrue: [^ dialectName := #Dolphin].
	self basicIsGNU ifTrue: [^ dialectName := #GNU].
	self basicIsVisualAge ifTrue: [^ dialectName := #VisualAge].
	self basicIsVisualWorks ifTrue: [^ dialectName := #VisualWorks].
	self basicIsSqueak ifTrue: [^ dialectName := #Squeak].
	self basicIsObjectStudio ifTrue: [^dialectName := #ObjectStudio].
	self error: 'I don''t know what dialect this is'.
	^ self! !

!Dialect class methodsFor: 'private' stamp: ' 5/6/05 12:11'!
lookedUpNames
	lookedUpNames isNil ifTrue: [lookedUpNames := IdentityDictionary new].
	^lookedUpNames.! !

!Dialect class methodsFor: 'private' stamp: ' 5/6/05 12:11'!
reset
	lookedUpNames := nil.
	identitySetClass := nil.
	timestampClass := nil.
	dialectName := nil.! !


!Dialect class methodsFor: 'numbers' stamp: ' 5/6/05 12:11'!
coerceToDoublePrecisionFloat: aNumber

	self isGNU ifTrue: [^ aNumber asFloatD].
	self isVisualWorks ifTrue: [^ aNumber asDouble].
	self isVisualAge ifTrue: [^ aNumber asDouble].
	self isSqueak ifTrue: [^aNumber asFloat].
	^ aNumber! !

!Dialect class methodsFor: 'numbers' stamp: ' 5/6/05 12:11'!
doesPrecisionOf: aNumber equal: aPrecision
	^aNumber class == self fixedPointClass and: [aNumber scale = aPrecision].! !

!Dialect class methodsFor: 'numbers' stamp: ' 5/6/05 12:11'!
doublePrecisionFloatClass

	self isGNU ifTrue: [^ self smalltalkAt: #FloatD].
	self isVisualWorks ifTrue: [^ self smalltalkAt: #Double].
	^ Float! !

!Dialect class methodsFor: 'numbers' stamp: ' 5/6/05 12:11'!
fixedPointClass
	Dialect isVisualWorks ifTrue: [^self smalltalkAt: #FixedPoint].! !

!Dialect class methodsFor: 'numbers' stamp: ' 5/6/05 12:11'!
singlePrecisionFloatClass
	^ Float! !


!Dialect class methodsFor: 'files' stamp: ' 5/6/05 12:11'!
contentsOfFileNamed: aString 
	"Given a text file name, read its contents"

	| stream contents fileClass |
	Dialect isVisualWorks ifTrue: [^aString asFilename contentsOfEntireFile].
	Dialect isSqueak ifTrue: [
		stream := (Dialect smalltalkAt: #CrLfFileStream) oldFileNamed: aString.
		[contents := stream contents] ensure: [stream close].
		^contents].

	fileClass := Dialect isVisualAge 
				ifTrue: [self smalltalkAt: #CfsReadFileStream]
				ifFalse: 
					[Dialect isDolphin ifTrue: [self smalltalkAt: #File] ifFalse: [self halt]].
	stream := fileClass read: aString.
	[contents := stream contents] ensure: [stream close].
	^contents! !


!Dialect class methodsFor: 'identifying' stamp: ' 5/6/05 12:11'!
dialectName

	dialectName isNil ifTrue: [self determineDialect.].
	^ dialectName! !

!Dialect class methodsFor: 'identifying' stamp: ' 5/6/05 12:11'!
isDolphin

	^ self dialectName = #Dolphin! !

!Dialect class methodsFor: 'identifying' stamp: ' 5/6/05 12:11'!
isGNU

	^ self dialectName = #GNU! !

!Dialect class methodsFor: 'identifying' stamp: ' 5/6/05 12:11'!
isObjectStudio

	^ self dialectName = #ObjectStudio! !

!Dialect class methodsFor: 'identifying' stamp: ' 5/6/05 12:11'!
isSqueak

	^ self dialectName = #Squeak! !

!Dialect class methodsFor: 'identifying' stamp: ' 5/6/05 12:11'!
isVisualAge

	^ self dialectName = #VisualAge! !

!Dialect class methodsFor: 'identifying' stamp: ' 5/6/05 12:11'!
isVisualWorks

	^ self dialectName = #VisualWorks! !


!Dialect class methodsFor: 'general portability' stamp: ' 5/6/05 12:11'!
error
    "For
        aTestCaseInstance should: aSomeBlock raise: Dialect error
    "
	^Dialect isVisualAge ifTrue: [^Error, ExError] ifFalse: [Error].! !

!Dialect class methodsFor: 'general portability' stamp: ' 5/6/05 12:11'!
fitHashIntoSmallInteger: aNumber
	"Truncate the number to fit into smallinteger range. Mostly useful for ObjectStudio where hashes have to be 16 bits or less"
	^Dialect isObjectStudio ifTrue: [aNumber hash] ifFalse: [aNumber].! !

!Dialect class methodsFor: 'general portability' stamp: ' 5/6/05 12:11'!
garbageCollect

	Dialect isGNU ifTrue: [^ ObjectMemory globalGarbageCollect].
	Dialect isVisualWorks ifTrue: [^ ObjectMemory quickGC].
	Dialect isVisualAge ifTrue: [^ (self smalltalkAt: #System) globalGarbageCollect].
	Dialect isSqueak ifTrue: [^Smalltalk garbageCollect].
	Dialect isObjectStudio ifTrue: [^(self smalltalkAt: #System) garbageCollect].
	self error: 'not implemented yet'.
	^ self! !

!Dialect class methodsFor: 'general portability' stamp: ' 5/6/05 12:11'!
identitySetClass
	identitySetClass == nil
		ifTrue:
			[Dialect isVisualAge
				ifTrue: [identitySetClass := self smalltalkAt: #EsIdentitySet]
				ifFalse: [identitySetClass := self smalltalkAt: #IdentitySet]].
	^identitySetClass.! !

!Dialect class methodsFor: 'general portability' stamp: ' 5/6/05 12:11'!
instVarNameFor: aName

	Dialect isGNU ifTrue: [^ aName asSymbol].
	^ aName asString! !

!Dialect class methodsFor: 'general portability' stamp: ' 5/6/05 12:11'!
isBlock: anObject
	"Return true if this is a block"
	self isVisualAge ifTrue: [^anObject isKindOf: (self smalltalkAt: #Block)].
	^anObject class == [] class.! !

!Dialect class methodsFor: 'general portability' stamp: ' 5/6/05 12:11'!
newIdentitySet
	^self identitySetClass new.! !

!Dialect class methodsFor: 'general portability' stamp: ' 5/6/05 12:11'!
smalltalkAssociationAt: aName

	^ self smalltalkAssociationAt: aName ifAbsent: [self error: 'element not found'.]! !

!Dialect class methodsFor: 'general portability' stamp: ' 5/6/05 12:11'!
smalltalkAssociationAt: aName ifAbsent: aBlock

	self isVisualWorks ifTrue: [^ aName asQualifiedReference].
	^ Smalltalk associationAt: aName asSymbol ifAbsent: aBlock! !

!Dialect class methodsFor: 'general portability' stamp: ' 5/6/05 12:11'!
smalltalkAt: aName

	^ self smalltalkAt: aName ifAbsent: [self error: 'element not found'].! !

!Dialect class methodsFor: 'general portability' stamp: ' 5/6/05 12:11'!
smalltalkAt: aName ifAbsent: aBlock
	"We may look these names up a lot, so cache them in a small, local dictionary"
	| cached value |
	cached := self lookedUpNames at: aName ifAbsent: [nil].
	cached isNil ifFalse: [^cached].
	value := self isVisualWorks
				ifTrue: [aName asQualifiedReference valueOrDo: aBlock]
				ifFalse: [Smalltalk at: aName asSymbol ifAbsent: aBlock].
	self lookedUpNames
		at: aName
		put: value.
	^value.! !

!Dialect class methodsFor: 'general portability' stamp: ' 5/6/05 12:11'!
tokensBasedOn: aString in: stringToTokenize

	self isGNU ifTrue: [^ stringToTokenize subStrings: aString first].
	self isVisualWorks ifTrue: [^ stringToTokenize tokensBasedOn: aString first].
	self isSqueak ifTrue: [^ stringToTokenize findTokens: aString].
	self isDolphin ifTrue: [^ stringToTokenize subStrings: aString].
	self isVisualAge ifTrue: [^ (stringToTokenize subStrings: aString first)].
	self isObjectStudio ifTrue: [^(stringToTokenize asArrayOfSubstringsDelimiter: aString first)].
	self error: 'not implemented yet'.
	^ self! !

!Dialect class methodsFor: 'general portability' stamp: ' 5/6/05 12:11'!
weakValueDictionaryClass

	Dialect isVisualWorks ifTrue: [^self smalltalkAt: #EphemeralValueDictionary].
	Dialect isSqueak ifTrue: [^self smalltalkAt: #WeakValueDictionary].
	self error: 'Not yet implemented for this dialect'.! !


!Dialect class methodsFor: 'forward references' stamp: ' 5/6/05 12:11'!
glorpConstantExpressionClass
	^ConstantExpression.! !


!Dialect class methodsFor: 'LICENSE' stamp: ' 5/6/05 12:11'!
LICENSE

	^ 'Copyright 2000-2004 Alan Knight.
This class is part of the GLORP system (see http://www.glorp.org), licensed under the GNU Lesser General Public License, with clarifications with respect to Smalltalk library usage (LGPL(S)). This code is distributed WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE . See the package comment, or the COPYING.TXT file that should accompany this distribution, or the GNU Lesser General Public License.'! !


!Dialect class methodsFor: 'collections' stamp: ' 5/6/05 12:11'!
needsCollectionMementoFor: aCollection
	^true.! !


!Dialect class methodsFor: 'binding' stamp: ' 5/6/05 12:11'!
unbindableClassNames

	self isVisualWorks ifTrue: [^ #()].
	^ #()! !


!Dialect class methodsFor: '*glorpPostload-override' stamp: 'rh 6/6/2005 02:22'!
argumentCountFor: aBlock

	Dialect isGNU ifTrue: [^ self error: 'not implemented yet'].
	Dialect isVisualWorks ifTrue: [^ aBlock numArgs].
	Dialect isVisualAge ifTrue: [^ aBlock argumentCount].
	Dialect isDolphin ifTrue: [^ aBlock argumentCount].
	Dialect isSqueak ifTrue: [^aBlock argumentCount].
	Dialect isObjectStudio ifTrue: [^aBlock numArgs].
	self error: 'not implemented yet'.
	^ self! !

!Dialect class methodsFor: '*glorpPostload-override' stamp: 'rh 6/5/2005 21:46'!
newDateWithYears: years months: months days: days

	self isVisualWorks ifTrue: [^ Date newDay: days monthNumber: months year: years].
	self isSqueak ifTrue: [^ Date newDay: days month: months year: years].
	self isGNU ifTrue: [^ Date newDay: days monthIndex: months year: years].
	self isVisualAge ifTrue: [^Date newDay: days monthIndex: months year: years].
	self isObjectStudio ifTrue: [^Date newDay: days imonth: months year: years].
	self error: 'not implemented'.
	^ self! !

!Dialect class methodsFor: '*glorpPostload-override' stamp: 'rh 6/9/2005 02:10'!
readFixedPointFrom: aString

	self isVisualWorks ifTrue: [^ (self smalltalkAt: #FixedPoint) readFrom: (ReadStream on: aString)].
	self isSqueak ifTrue: [^ (Number readFrom: aString , 's0') asScaledDecimal:
				aString size - (aString indexOf: $. ifAbsent: [aString size])].
	self isDolphin ifTrue: [^ Number readFrom: (ReadStream on: aString , 's')].
	self isGNU
		ifTrue: [
			^ (Number readFrom: (ReadStream on: aString)) asScaledDecimal:
				aString size - (aString indexOf: $. ifAbsent: [aString size.])
		].
	self isVisualAge ifTrue: [ ^(self smalltalkAt: #Decimal) fromString: aString].
	self isObjectStudio ifTrue: [^(self smalltalkAt: #Decimal) newString: aString].
	self error: 'not implemented'.
	^ self! !
-------------- next part --------------
'From Squeak3.10alpha.7068 of 2 February 2007 [latest update: #7068] on 28 February 2007 at 12:46:13 pm'!
SqueakDatabaseAccessor subclass: #Squeak39DatabaseAccessor
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Glorp-Database'!

!Squeak39DatabaseAccessor methodsFor: 'executing' stamp: 'mhb 2/8/2007 17:17'!
basicExecuteSQLString: aString 
	"convert the SQL stream to utf8"
	| result rowCollection |
	result := connection
				execute: (aString asWideString convertToEncoding: 'utf-8').
	result errorResponse notNil
		ifTrue: [self externalDatabaseErrorSignal signal: result errorResponse value].
	rowCollection := OrderedCollection new.
	result rows
		do: [:ea | rowCollection add: ea data asArray].
	^ ReadStream on: rowCollection asArray! !


More information about the Seaside mailing list