[BUG] Cannot connect to 127.0.0.1:45677 Re: [ANN] RMT (RemoteMessaging Toolkit)

Lic. Edgar J. De Cleene edgardec2001 at yahoo.com.ar
Sat Apr 3 11:39:51 UTC 2004


On 03/04/04 06:10, "Masashi Umezawa" <umejava at mars.dti.ne.jp> wrote:

> I brought up my old iBook and tested.
Good you have one (me too and that is with 9.1)
My test.
On iBook with 9.1 , work as you said.
On iMac 2 with 10.2.6 don¹t work.
If you look in example of TcpService and see

| count listener |
    count _ 0.
    listener _ ComancheListener
        on: 8123
        handler: 
            [ :socket |
            count _ count + 1.
            Transcript show: socket getData.
            socket closeAndDestroy].
    listener forkAndListenWhile: [count < 5].

In 3.7 we don't have getData , so I load my RemoteExperiments, This is a
elemental little toy for command SqueakLight server from a regular image.
Uses a couple of methods from rST by Diego Gomez Deck.
Lets send and receive objects and with String compiler in remote you can do
nice tricks.
This works fine , but not example.
I attach, just in case.

And finally, I load in 3.6 and guess what. Your code works as you design.
So , problem remains in 3.7 and OS X 10.2.6 and maybe rewrite of Sockets
stuff change for worst, some code derived stop working.

Cheers and don't trash your iBook !
Edgar

-------------- next part --------------
'From Squeak3.7alpha of ''11 September 2003'' [latest update: #5657] on 8 March 2004 at 9:14:54 am'!
Object subclass: #RemoteClient
	instanceVariableNames: 'socket serverName'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'RemoteExperiments'!

!RemoteClient methodsFor: 'as yet unclassified' stamp: 'edc 2/16/2004 10:04'!
initialize
	| command |
	Transcript open.
	Transcript show: 'starting remote comm test';
		 cr.
	Transcript show: 'initializing network ... '.
	Socket initializeNetwork.
	Transcript show: 'ok';
		 cr.
	serverName := 'localhost'.
	command := FillInTheBlank request: 'Type remote image command' initialAnswer: ''.
	socket := Socket newTCP.
	socket
		connectTo: (NetNameResolver addressForName: serverName)
		port: 8000.
	socket waitForConnectionUntil: Socket standardDeadline.
	Transcript show: 'server start to perform instructions';
		 cr.
		self nextCommand: command! !

!RemoteClient methodsFor: 'as yet unclassified' stamp: 'edc 2/16/2004 10:18'!
newCommand
| command |
command := FillInTheBlank request: 'Type remote image command' initialAnswer: ''.
command = 'FIN' ifFalse: [
self nextCommand: command]! !

!RemoteClient methodsFor: 'as yet unclassified' stamp: 'edc 2/16/2004 10:20'!
nextCommand: command 
	| objRec |
	(socket isValid
			and: [socket isConnected])
		ifTrue: [Transcript show: 'Command sended is ' , command;
				 cr.
			socket sendObject: command]
		ifFalse: ["stale connection"
			socket destroy.
			socket := nil].
	[socket dataAvailable] whileFalse.
	objRec := socket getObject.
	Transcript show: 'Resoonse is ' , objRec printString;
										 cr.
	self newCommand! !


!RemoteClient class methodsFor: 'as yet unclassified' stamp: 'edc 2/16/2004 09:53'!
new
super new initialize! !


!Socket methodsFor: 'receiving' stamp: 'edc 2/15/2004 09:17'!
getData
	| t1 t2 |
	(self waitForDataUntil: Socket standardDeadline)
		ifFalse: [self error: 'getData timeout'].
	t1 _ String new: 4000.
	t2 _ self
				primSocket: socketHandle
				receiveDataInto: t1
				startingAt: 1
				count: t1 size.
	^ t1 copyFrom: 1 to: t2! !

!Socket methodsFor: 'waiting' stamp: 'jm 3/2/98 18:15'!
waitForConnectionUntil: deadline
	"Wait up until the given deadline for a connection to be established. Return true if it is established by the deadline, false if not."

	| status |
	status _ self primSocketConnectionStatus: socketHandle.
	[(status = WaitingForConnection) and: [Time millisecondClockValue < deadline]]
		whileTrue: [
			semaphore waitTimeoutMSecs: (deadline - Time millisecondClockValue).
			status _ self primSocketConnectionStatus: socketHandle].

	^ status = Connected! !

!Socket methodsFor: 'waiting' stamp: 'edc 2/15/2004 09:19'!
waitForDataUntil: deadline 
	"Wait up until the given deadline for data to arrive. Return true if data 
	arrives by the deadline, false if not."
	| dataArrived |
	[self isConnected & (dataArrived := self primSocketReceiveDataAvailable: socketHandle) not
		and: ["Connection end and final data can happen fast, so test in this 
			order "
			Time millisecondClockValue < deadline]]
		whileTrue: [self readSemaphore waitTimeoutMSecs: deadline - Time millisecondClockValue].
	^ dataArrived! !

!Socket methodsFor: 'sending-receiving objects' stamp: 'dgd 2/22/2002 20:28'!
getObject
	"gets a serialized object from this socket"
	| encoded object |
	encoded _ String new writeStream.
	[encoded size isZero]
		whileTrue: [encoded nextPutAll: self getData].
	[self isConnected
		and: [self dataAvailable]]
		whileTrue: [encoded nextPutAll: self getData].
	object _ ReferenceStream unStream: encoded contents.
	^ object! !

!Socket methodsFor: 'sending-receiving objects' stamp: 'dgd 2/22/2002 20:28'!
sendObject: anObject 
	"sends a serialized object to this socket"
	| encoded |
	encoded _ ReferenceStream streamedRepresentationOf: anObject.
	self sendData: encoded! !


!Socket class methodsFor: 'as yet unclassified' stamp: 'edc 2/15/2004 10:53'!
remoteCommClient
	| newSocket objRec command serverName |
	Transcript open.
	Transcript show: 'starting remote comm test';
		 cr.
	Transcript show: 'initializing network ... '.
	Socket initializeNetwork.
	Transcript show: 'ok';
		 cr.
	serverName := '169.254.6.4'.
	command := FillInTheBlank request: 'Type remote image command' initialAnswer: ''.
	newSocket := Socket newTCP.
	newSocket
		connectTo: (NetNameResolver addressForName: serverName)
		port: 8000.
	newSocket waitForConnectionUntil: Socket standardDeadline.
	Transcript show: 'server start to perform instructions';
		 cr.
	[command = 'FIN']
		whileFalse: [Transcript show: 'Command sended is ' , command;
				 cr.
			newSocket sendObject: command.
			newSocket
				waitForConnectionUntil: (Socket deadlineSecs: 60).
			[newSocket isConnected]
				whileTrue: [newSocket dataAvailable
						ifTrue: [newSocket dataAvailable
								ifTrue: [objRec := newSocket getObject.
									Transcript show: 'Resoonse is ' , objRec printString;
										 cr.
									command := FillInTheBlank request: 'Type remote image command' initialAnswer: '']]]].
	newSocket closeAndDestroy! !



More information about the Squeak-dev mailing list