[GOODIE] patch PostgreSQL client to work on Squat

Yanni Chiu yanni at rogers.com
Wed Feb 18 03:48:48 UTC 2004


PGConnectionUsingFlow simply subclasses the PGConnection
to override a few methods to work with the Flow networking
protocol.

The pgflow.cs contains a few loose methods on Transcript,
Collection, String and Character.

The test cases should pass if you change PGConnection
and the tests to use Date instead of DateAndTime.
Also needed to make the tests pass is to add the method
ByteArray>>unsignedLongAt:put:bigEndian (and change the
test to use it instead of unsignedLongAt:put:, which
calls the FFI plugin).

I tested on WinXP Pro and x86 Linux.

--yanni
-------------- next part --------------
'From Squeak 2.2 of Sept 23, 1998 on 17 February 2004 at 10:03:47 pm'!
PGConnection subclass: #PGConnectionUsingFlow
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'PostgreSQLClient'!

!PGConnectionUsingFlow methodsFor: 'as yet unclassified'!
closeSocket: aSocket

	trace >= 2
		ifTrue: [ self log: 'closeSocket' text: 'hostname: ', connectionArgs hostname, ':', connectionArgs portno printString ].
	trace >= 2
		ifTrue: [ self log: 'closeSocket' text: 'socket: ', aSocket printString ].

	aSocket close. "closeAndDestroy."

	trace >= 2
		ifTrue: [ self log: 'closeSocket' text: 'socket: ', aSocket printString ].
! !

!PGConnectionUsingFlow methodsFor: 'as yet unclassified'!
copyInDataRows
	"copyStream is initially positioned at the start of a data rows stream.
	The contents are sent down the socket.

	In a stream of data rows, each row is terminatated by a Byte1('\n').
	A sequence of Byte1('\\'), Byte1('.'), Byte1('\n') is the last line.
	"

	trace >= 8
		ifTrue: [ self log: 'copyInDataRows' text: copyStream contents printString ].

	socket nextPutAll: copyStream contents.
	"socket sendData: (String with: $\ with: $. with: Character lf)."
! !

!PGConnectionUsingFlow methodsFor: 'as yet unclassified'!
isConnected
	^ socket notNil "and: [ socket isConnected]"! !

!PGConnectionUsingFlow methodsFor: 'as yet unclassified'!
next
	readIndex >= lastReadIndex 
		ifTrue: 
			[trace >= 10 
				ifTrue: [self log: 'next' text: '**** filling read buffer ****'].
			"(Delay forMilliseconds: 500) wait."
			"socket waitForDataFor: Socket standardDeadline."
			
			[| buf |
			buf := socket nextAvailable.
			(lastReadIndex := buf size) = 0 
				ifTrue: 
					[trace >= 10 
						ifTrue: [self log: 'next' text: '**** zero length received from socket ****'].
					(Delay forMilliseconds: 100) wait]
				ifFalse: [readBuffer replaceFrom: 1 to: buf size with: buf startingAt: 1 ].
			lastReadIndex = 0] 
					whileTrue.
			readIndex := 0.
			trace >= 10 
				ifTrue: 
					[self log: 'next' text: '**** read ' , lastReadIndex printString , ' ****']].
	readIndex := readIndex + 1.
	trace >= 10 
		ifTrue: 
			[self log: 'next'
				text: 'readIndex=' , readIndex printString , ',lastReadIndex=' 
						, lastReadIndex printString , ',ch=' 
						, (readBuffer at: readIndex) printString].
	^readBuffer at: readIndex! !

!PGConnectionUsingFlow methodsFor: 'as yet unclassified'!
openSocket
	| newSocket |
	trace >= 2 
		ifTrue: 
			[self log: 'openSocket'
				text: 'hostname: ' , connectionArgs hostname , ':' 
						, connectionArgs portno printString].

	newSocket := TCPStream clientToAddress: (
			SocketAddressResolver
				addressForPort: connectionArgs portno
				atHostNamed: connectionArgs hostname
			).
	newSocket beBinary.

	trace >= 2 
		ifTrue: [self log: 'openSocket' text: 'socket: ' , newSocket printString].
	^newSocket! !

!PGConnectionUsingFlow methodsFor: 'as yet unclassified'!
sendPacket: aPacket on: aSocket

	| s |
	s := WriteStream on: String new.
	aPacket writeOn: s.

	trace >= 5
		ifTrue: [
			self log: 'sendPacket' text: aPacket printString.
			trace >= 10 ifTrue: [self log: 'sendPacket' text: s contents printString].
		].

	aSocket nextPutAll: s contents.
! !
-------------- next part --------------
'From Squeak 2.2 of Sept 23, 1998 on 17 February 2004 at 10:02:46 pm'!
!Character methodsFor: 'as yet unclassified'!
codePoint
	"Return the encoding value of the receiver."
	#Fundmntl.
	^ self asciiValue! !
!TranscriptStream methodsFor: 'as yet unclassified'!
flush
	self endEntry! !
!String methodsFor: 'as yet unclassified'!
asInteger 
	"Answer the Integer created by interpreting the receiver as the string representation of an integer.  Answer nil if no digits, else find the first digit and then all consecutive digits after that"

	| startPosition tail endPosition |
	startPosition _ self findFirst: [:ch | ch isDigit].
	startPosition == 0 ifTrue: [^ nil].
	tail _ self copyFrom: startPosition to: self size.
	endPosition _ tail findFirst: [:ch | ch isDigit not].
	endPosition == 0 ifTrue: [endPosition _ tail size + 1].
	^ Number readFromString: (tail copyFrom: 1 to: endPosition - 1)

"
'1796exportFixes-tkMX' asInteger
'1848recentLogFile-sw'  asInteger
'donald' asInteger
'abc234def567' asInteger
"! !
!String methodsFor: 'as yet unclassified'!
subStrings
	"Answer an array of the substrings that compose the receiver."
	#Collectn.
	"Added 2000/04/08 For ANSI <readableString> protocol."
	^ self substrings! !
!String methodsFor: 'as yet unclassified'!
substrings
	"Answer an array of the substrings that compose the receiver."
	| result end beginning |

	result _ WriteStream on: (Array new: 10).



	end _ 0.
	"find one substring each time through this loop"
	[ 
		"find the beginning of the next substring"
		beginning _ self indexOfAnyOf: CSNonSeparators startingAt: end+1 ifAbsent: [ nil ].
		beginning ~~ nil ] 
	whileTrue: [
		"find the end"
		end _ self indexOfAnyOf: CSSeparators startingAt: beginning ifAbsent: [ self size + 1 ].
		end _ end - 1.

		result nextPut: (self copyFrom: beginning to: end).

	].


	^result contents! !
!String methodsFor: 'as yet unclassified'!
subStrings: separators 
	"Answer an array containing the substrings in the receiver separated 
	by the elements of separators."
	| char result sourceStream subString |
	#Collectn.
	"Changed 2000/04/08 For ANSI <readableString> protocol."
	(separators allSatisfy: [:element | element isKindOf: Character])
		ifFalse: [^ self error: 'separators must be Characters.'].
	sourceStream := ReadStream on: self.
	result := OrderedCollection new.
	subString := String new.
	[sourceStream atEnd]
		whileFalse: 
			[char := sourceStream next.
			(separators includes: char)
				ifTrue: [subString notEmpty
						ifTrue: 
							[result add: subString copy.
							subString := String new]]
				ifFalse: [subString := subString , (String with: char)]].
	subString notEmpty ifTrue: [result add: subString copy].
	^ result asArray! !
!Collection methodsFor: 'as yet unclassified'!
notEmpty
	"Answer whether the receiver contains any elements."

	^ self isEmpty not! !
!Collection methodsFor: 'as yet unclassified'!
allSatisfy: aBlock
	"Evaluate aBlock with the elements of the receiver.
	If aBlock returns false for any element return false.
	Otherwise return true."

	self do: [:each | (aBlock value: each) ifFalse: [^ false]].
	^ true! !


More information about the Squeak-dev mailing list