[BUG][FIX] Socket and SocketStream Fixes (for releases 3.6 and beyond)

Stephen Pair stephen at pairhome.net
Thu Oct 30 13:43:02 UTC 2003


Attached is a changeset that fixes and enhances a few things Socket and 
SocketStream.  This changeset is currently installed with Comanche 6.2.  
Here is a brief summary of the changes:

----- Socket changes -----
-- instance side --
#receiveDataInto:startingAt: - modified such that it does not signal a 
connection closed exception and instead will go ahead and receive data 
even though the socket is closed (thus, this method no longer assumes 
that a closed socket doesn't have data available)

#receiveDataTimeout:
#receiveDataTimeout: timeout into:
#receiveDataWithTimeoutInto:startingAt: - comments updated to reflect 
that these methods do not signal an exception

#receiveDataTimeout:into:startingAt: - modified such that the timeout is 
obeyed, even in the case where there is no data coming into the socket, 
yet it remains open (the current version would loop indefinitely, 
ignoring the timeout).  Also modified such that it does not signal an 
exception for time out or connection closed...thus, callers to this 
method must test for connection closed rather than handle a 
ConnectionClosed exception (which necessitates the FTPClient fixes)

#waitForData - redefined in terms of a new method called 
#waitForDataIfClosed:

#waitForDataIfClosed: - new method that accept a block that will be 
evaluated in the event the socket is closed while waiting for data

#waitForDisconnectionFor: - eliminated a call to #inform: that could pop 
open a dialog if there are extra bytes pending on the socket

-- class side --
(no changes)

----- SocketStream changes -----
-- instance side --
#next - adds a test to see if the stream is #atEnd after the #receive data

#next: - adds an #atEnd test to ensure we don't loop infinitely

#peekFor: - new method that works like other #peekFor: methods

#peekForAll: - new method that tests to see if the next characters in 
the stream match the argument and if so, move the position past those 
characters and return true, if not, leave the receiver untouched and 
return false

#upToAll: - adds an #atEnd test that prevents an infinite looping in 
certain circumstances...fixes a case where if there is no data available 
on the socket, we try to "#copyFrom: 1 to: -1" (which causes an error)

-- class side --
(no changes)

----- FTPClient changes -----
-- instance side --
get:dataInto:
getDataInto: - both methods are modified to test for connection closed 
rather than rely on a ConnectionClosed exception (which is no longer 
signaled)

-- class side --
(no changes)
-------------- next part --------------

!FTPClient methodsFor: 'private protocol' stamp: 'svp 10/28/2003 11:06'!
get: limit dataInto: dataStream
	"Reel in data until the server closes the connection or the limit is reached.
	At the same time, watch for errors on otherSocket."

	| buf bytesRead currentlyRead |
	currentlyRead _ 0.
	buf _ String new: 4000.
	[currentlyRead < limit and: 
	[self dataSocket isConnected or: [self dataSocket dataAvailable]]]
		whileTrue: [
			self checkForPendingError.
			bytesRead _ self dataSocket receiveDataWithTimeoutInto: buf.
			1 to: (bytesRead min: (limit - currentlyRead)) do: [:ii | dataStream nextPut: (buf at: ii)].
			currentlyRead _ currentlyRead + bytesRead].
	dataStream reset.	"position: 0."
	^ dataStream! !

!FTPClient methodsFor: 'private protocol' stamp: 'svp 10/28/2003 11:04'!
getDataInto: dataStream
	"Reel in all data until the server closes the connection.  At the same time, watch for errors on otherSocket.  Don't know how much is coming.  Put the data on the stream."

	| buf bytesRead |
	buf _ String new: 4000.
	[self dataSocket isConnected or: [self dataSocket dataAvailable]]
		whileTrue: [
			self checkForPendingError.
			bytesRead _ self dataSocket receiveDataWithTimeoutInto: buf.
			1 to: bytesRead do: [:ii | dataStream nextPut: (buf at: ii)]].
	dataStream reset.	"position: 0."
	^ dataStream! !


!Socket methodsFor: 'receiving' stamp: 'svp 9/23/2003 00:12'!
receiveDataInto: aStringOrByteArray startingAt: aNumber
	"Receive data into the given buffer and return the number of bytes received. 
	Note the given buffer may be only partially filled by the received data.
	Waits for data once.  The answer may be zero (indicating that no data was 
	available before the socket closed)."

	| bytesRead closed |
	bytesRead := 0.
	closed := false.
	[closed not and: [bytesRead == 0]]
		whileTrue: [
			self waitForDataIfClosed: [closed := true].
			bytesRead := self primSocket: socketHandle
				receiveDataInto: aStringOrByteArray
				startingAt: aNumber
				count: aStringOrByteArray size-aNumber+1].
	^bytesRead
! !

!Socket methodsFor: 'receiving' stamp: 'svp 9/23/2003 00:03'!
receiveDataTimeout: timeout
	"Receive data into the given buffer and return the number of bytes received. 
	Note the given buffer may be only partially filled by the received data.
	Waits for data once."

	| buffer bytesRead |
	buffer _ String new: 2000.
	bytesRead _ self receiveDataTimeout: timeout into: buffer.
	^buffer copyFrom: 1 to: bytesRead! !

!Socket methodsFor: 'receiving' stamp: 'svp 9/23/2003 00:01'!
receiveDataTimeout: timeout into: aStringOrByteArray 
	"Receive data into the given buffer and return the number of bytes received. 
	Note the given buffer may be only partially filled by the received data.
	Waits for data once."

	^self receiveDataTimeout: timeout into: aStringOrByteArray startingAt: 1! !

!Socket methodsFor: 'receiving' stamp: 'svp 9/22/2003 23:58'!
receiveDataTimeout: timeout into: aStringOrByteArray startingAt: aNumber
	"Receive data into the given buffer and return the number of bytes received. 
	Note the given buffer may be only partially filled by the received data.
	Wait for data once for the specified nr of seconds.  The answer may be 
	zero (indicating that there was no data available within the given timeout)."

	self waitForDataFor: timeout ifClosed: [] ifTimedOut: [].
	^self primSocket: socketHandle
		receiveDataInto: aStringOrByteArray
		startingAt: aNumber
		count: aStringOrByteArray size-aNumber+1
! !

!Socket methodsFor: 'receiving' stamp: 'svp 9/23/2003 00:01'!
receiveDataWithTimeoutInto: aStringOrByteArray startingAt: aNumber
	"Receive data into the given buffer and return the number of bytes received. 
	Note the given buffer may be only partially filled by the received data.
	Waits for data once."

	^self receiveDataTimeout: Socket standardTimeout into: aStringOrByteArray startingAt: aNumber 
! !

!Socket methodsFor: 'waiting' stamp: 'svp 9/23/2003 00:09'!
waitForData
	"Wait for data to arrive.  This method will block until
	data is available or the socket is closed.  If the socket is closed
	a ConnectionClosed exception will be signaled."

	^self waitForDataIfClosed:
		[ConnectionClosed signal: 'Connection close while waiting for data.']! !

!Socket methodsFor: 'waiting' stamp: 'svp 9/23/2003 00:08'!
waitForDataIfClosed: closedBlock
	"Wait indefinitely for data to arrive.  This method will block until
	data is available or the socket is closed."

	[true]
		whileTrue: [
			(self primSocketReceiveDataAvailable: socketHandle)
				ifTrue: [^self].
			self isConnected
				ifFalse: [^closedBlock value].
			self readSemaphore wait].
! !

!Socket methodsFor: 'waiting' stamp: 'svp 9/22/2003 23:37'!
waitForDisconnectionFor: timeout
	"Wait up until the given deadline for the the connection to be broken. Return true if it is broken by the deadline, false if not."
	"Note: The client should know the the connect is really going to be closed (e.g., because he has called 'close' to send a close request to the other end) before calling this method.
JMM 00/5/17 note that other end can close which will terminate wait"

	| extraBytes status deadline |
	extraBytes _ 0.
	status _ self primSocketConnectionStatus: socketHandle.
	deadline := Socket deadlineSecs: timeout.
	[((status = Connected) or: [(status = ThisEndClosed)]) and:
	 [Time millisecondClockValue < deadline]] whileTrue: [
		self dataAvailable
			ifTrue: [extraBytes _ extraBytes + self discardReceivedData].
		semaphore waitTimeoutMSecs: (deadline - Time millisecondClockValue).
		status _ self primSocketConnectionStatus: socketHandle].

	^ status ~= Connected
! !


!SocketStream methodsFor: 'stream in' stamp: 'svp 9/20/2003 14:16'!
next
	self atEnd ifTrue: [^nil].
	self inStream atEnd ifTrue: 
		[self receiveData.
		self atEnd ifTrue: [^nil]].
	^self inStream next! !

!SocketStream methodsFor: 'stream in' stamp: 'svp 9/19/2003 23:48'!
next: anInteger
	"Answer anInteger bytes of data."
	[self atEnd not and: [self inStream size - self inStream position < anInteger]]
		whileTrue: [self receiveData].
	^self inStream next: anInteger! !

!SocketStream methodsFor: 'stream in' stamp: 'svp 10/28/2003 11:30'!
peekFor: aCharacter
	self atEnd ifTrue: [^false].
	self inStream atEnd ifTrue: 
		[self receiveData.
		self atEnd ifTrue: [^false]].
	^self inStream peekFor: aCharacter! !

!SocketStream methodsFor: 'stream in' stamp: 'svp 10/28/2003 11:41'!
peekForAll: aString
	"<Boolean> Answer whether or not the next string of characters in the receiver
	matches aString.  If a match is made, advance over that string in the receiver and
	answer true.  If no match, then leave the receiver alone and answer false."

	| start tmp |
	[self atEnd not and: [self inStream size - self inStream position < aString size]]
		whileTrue: [self receiveData].
	(self inStream size - self inStream position) >= aString size ifFalse: [^false].
	start := self inStream position + 1.
	tmp := self inStream contents 
		copyFrom: start
		to: (start + aString size - 1).
	tmp = aString ifFalse: [^false].
	self next: aString size.
	^true
! !

!SocketStream methodsFor: 'stream in' stamp: 'svp 9/23/2003 02:40'!
upToAll: delims
	| searchBuffer index |
	searchBuffer _ String new.
	[searchBuffer _ searchBuffer , self inStream upToEnd.
	self resetInStream.
	index _ searchBuffer indexOfSubCollection: delims startingAt: 1.
	index = 0 and: [self atEnd not]]
		whileTrue: [self receiveData].

	index = 0 
		ifTrue: [index := 0 max: searchBuffer size]
		ifFalse:
			[self pushBack: (searchBuffer copyFrom: index + delims size to: searchBuffer size)].
	^searchBuffer copyFrom: 1 to: (0 max: index-1)! !

!SocketStream methodsFor: 'stream in' stamp: 'svp 10/28/2003 12:58'!
upToEnd
	"Answer a subcollection from the current access position through the last element of the receiver."
	| resultStream |
	resultStream _ WriteStream on: (String new: 100).
	[resultStream nextPutAll: self inStream upToEnd.
	self atEnd not or: [self isDataAvailable]]
		whileTrue: [self receiveData].
	^resultStream contents! !



More information about the Squeak-dev mailing list