[ENH] Socks

Michael Rueger Michael.Rueger.-ND at disney.com
Wed Mar 8 21:10:00 UTC 2000


Hi all,

no, I'm not talking about getting ready for Santa ;-)

Attached is a change set containing a first stab at the socks firewall
tunneling protocol.

Enjoy

Michael

-----------------

Change Set:		Socks-mir
Date:			8 March 2000
Author:			Michael Rueger

This change set adds a first version of the socks4 and socks5 firewall
tunneling protocol.
The socks5 implementation is somewhat rudimentary but is usable.

To test it:
Change the TelnetMachine>>connect method from
	socket _ Socket new.
to
	socket _ SocksSocket new.
	socket socks4.

Make sure to set a proxy host first.


-- 

 "To improve is to change, to be perfect is to change often." 
                                            Winston Churchill
+------------------------------------------------------------+
| Michael Rueger                                             |
| Phone: ++1 (818) 623 3283        Fax:   ++1 (818) 623 3559 |
+---------- Michael.Rueger.-ND at corp.go.com ------------------+
-------------- next part --------------
"Change Set:		Socks-mir
Date:			8 March 2000
Author:			Michael Rueger

This change set adds a first version of the socks4 and socks5 firewall tunneling protocol.
The socks5 implementation is somewhat rudimentary but is usable.

To test it:
Change the TelnetMachine>>connect method from
	socket _ Socket new.
to
	socket _ SocksSocket new.
	socket socks4.

Make sure to set a proxy host first.
"!

Socket subclass: #SocksSocket
	instanceVariableNames: 'vers method socksIP socksPort dstPort dstIP dstName '
	classVariableNames: 'DefaultSocksHostName DefaultSocksPort '
	poolDictionaries: ''
	category: 'Network-Kernel'!

!HTTPSocket class methodsFor: 'proxy settings' stamp: 'mir 3/7/2000 12:58'!
proxyServer
	^HTTPProxyServer! !


!SocksSocket commentStamp: 'mir 3/6/2000 15:00' prior: 0!
This class implements the socks 4 and partially socks 5 connection protocol.
For backward compatibility the socks protocol is disabled by default, so subclasses still work.
For further documentation check out:

Socks4: http://spiderman.socks.nec.com/protocol/socks4.protocol

Socks5: http://spiderman.socks.nec.com/rfc/rfc1928.txt!


!SocksSocket methodsFor: 'methods' stamp: 'mir 3/6/2000 13:24'!
noAutorizationMethod
	^0! !

!SocksSocket methodsFor: 'private' stamp: 'mir 3/6/2000 13:34'!
connectCommandCode
	^1! !

!SocksSocket methodsFor: 'private' stamp: 'mir 3/6/2000 14:51'!
defaultSocksHostAddress

	Socket initializeNetwork.
	^NetNameResolver addressForName: DefaultSocksHostName! !

!SocksSocket methodsFor: 'private' stamp: 'mir 3/6/2000 14:52'!
defaultSocksPort
	^DefaultSocksPort! !

!SocksSocket methodsFor: 'private' stamp: 'mir 3/6/2000 15:07'!
defaultTimeOutDuration
	^20000! !

!SocksSocket methodsFor: 'private' stamp: 'mir 3/6/2000 15:29'!
dstIP
	^dstIP! !

!SocksSocket methodsFor: 'private' stamp: 'mir 3/6/2000 14:03'!
requestGrantedCode
	^90! !

!SocksSocket methodsFor: 'private' stamp: 'mir 3/6/2000 15:11'!
socksError: errorString
	self close; destroy.
	self error: errorString! !

!SocksSocket methodsFor: 'private' stamp: 'mir 3/6/2000 17:46'!
waitForReply: replySize for: timeOutDuration

	| startTime response delay bytesRead |
	startTime _ Time millisecondClockValue.
	response _ ByteArray new: replySize.
	bytesRead _ 0.
	delay _ Delay forMilliseconds: 500.
	[bytesRead < replySize
		and: [(Time millisecondClockValue - startTime) < timeOutDuration]] whileTrue: [
		bytesRead _ bytesRead + (self receiveDataInto: response).
		delay wait.
		Transcript show: '.'].
	bytesRead < replySize
		ifTrue: [
			self close; destroy.
			^self error: 'Connection failed'].
	^response! !

!SocksSocket methodsFor: 'socks5' stamp: 'mir 3/6/2000 17:42'!
connectSocks5
	self
		socks5MethodSelection;
		sendSocks5ConnectionRequest;
		socks5RequestReply
! !

!SocksSocket methodsFor: 'socks5' stamp: 'mir 3/6/2000 17:29'!
hostIP6Code
	^4! !

!SocksSocket methodsFor: 'socks5' stamp: 'mir 3/6/2000 15:20'!
hostIPCode
	^1! !

!SocksSocket methodsFor: 'socks5' stamp: 'mir 3/6/2000 15:15'!
qualifiedHostNameCode
	^3! !

!SocksSocket methodsFor: 'socks5' stamp: 'mir 3/6/2000 17:25'!
sendSocks5ConnectionRequest
	"Once the method-dependent subnegotiation has completed, the client
   sends the request details."

	| requestString |
	requestString _ WriteStream on: ByteArray new.
	requestString
		nextPut: 5;
		nextPut: self connectCommandCode;
		nextPut: 0. "Reserved slot"
	dstName isNil
		ifTrue: [
			requestString
				nextPutAll: self hostIPCode;
				nextPutAll: dstIP]
		ifFalse: [
			requestString
				nextPut: self qualifiedHostNameCode;
				nextPut: dstName size;
				nextPutAll: dstName asByteArray].
	requestString nextWordPut: dstPort.
	self sendData: requestString contents! !

!SocksSocket methodsFor: 'socks5' stamp: 'mir 3/6/2000 17:35'!
skipQualifiedHostName

	| startTime response bytesRead |
	startTime _ Time millisecondClockValue.
	response _ ByteArray new: 1.

	[(bytesRead _ self receiveDataInto: response) < 1
		and: [(Time millisecondClockValue - startTime) < self defaultTimeOutDuration]] whileTrue.

	bytesRead < 1
		ifTrue: [self socksError: 'Time out reading data'].

	self waitForReply: (response at: 1) + 2 for: self defaultTimeOutDuration! !

!SocksSocket methodsFor: 'socks5' stamp: 'mir 3/6/2000 15:16'!
socks5MethodSelection
	"The client connects to the server, and sends a version
   identifier/method selection message.
	The server selects from one of the methods given in METHODS, and
   sends a METHOD selection message."

	| requestString response |
	requestString _ WriteStream on: ByteArray new.
	requestString
		nextPut: 5;
		nextPut: 1;
		nextPut: 0.
	self sendData: requestString contents.

	response _ self waitForReply: 2 for: self defaultTimeOutDuration.
	(response at: 2) == 16rFF
		ifTrue: [self socksError: 'No acceptable methods.']
		ifFalse: [method _ response at: 2]! !

!SocksSocket methodsFor: 'socks5' stamp: 'mir 3/6/2000 17:28'!
socks5RequestReply

	| response |
	response _ self waitForReply: 4 for: self defaultTimeOutDuration.
	"Skip rest for now."
	(response at: 4) = self hostIPCode
		ifTrue: [self waitForReply: 6 for: self defaultTimeOutDuration].
	(response at: 4) = self qualifiedHostNameCode
		ifTrue: [self skipQualifiedHostName].
	(response at: 4) = self hostIP6Code
		ifTrue: [self waitForReply: 18 for: self defaultTimeOutDuration].
	(response at: 2) ~= 0
		ifTrue: [^self socksError: 'Connection failed: ', (response at: 2) printString].
! !

!SocksSocket methodsFor: 'socks4' stamp: 'mir 3/6/2000 15:07'!
connectSocks4
	self
		sendSocks4ConnectionRequestUserId: '';
		waitForSocks4ConnectionReply.
! !

!SocksSocket methodsFor: 'socks4' stamp: 'mir 3/6/2000 16:11'!
sendSocks4ConnectionRequestUserId: userId
	"The client connects to the SOCKS server and sends a CONNECT request when
it wants to establish a connection to an application server. The client
includes in the request packet the IP address and the port number of the
destination host, and userid, in the following format.

	+----+----+----+----+----+----+----+----+----+----+....+----+
	| VN | CD | DSTPORT |      DSTIP        | USERID       |NULL|
	+----+----+----+----+----+----+----+----+----+----+....+----+
	   1    1      2              4           variable       1
	"

	| requestString |
	requestString _ WriteStream on: ByteArray new.
	dstIP ifNil: [
		Socket initializeNetwork.
		dstIP _ NetNameResolver addressForName: dstName].
	requestString
		nextPut: 4;
		nextPut: self connectCommandCode;
		nextWordPut: dstPort;
		nextPutAll: self dstIP;
		nextPutAll: userId asByteArray;
		nextPut: 0.
	self sendData: requestString contents! !

!SocksSocket methodsFor: 'socks4' stamp: 'mir 3/6/2000 15:11'!
waitForSocks4ConnectionReply

	| response |
	response _ self waitForReply: 8 for: self defaultTimeOutDuration.

	(response at: 2) = self requestGrantedCode
		ifFalse: [^self socksError: 'Connection failed: ' , (response at: 2) printString].! !

!SocksSocket methodsFor: 'initialize' stamp: 'mir 3/6/2000 14:52'!
initialize: socketType
	super initialize: socketType.
	self socks4.
	socksIP _ self defaultSocksHostAddress.
	socksPort _ self defaultSocksPort! !

!SocksSocket methodsFor: 'initialize' stamp: 'mir 3/6/2000 14:51'!
socks4
	vers _ 4.
	method _ nil.
! !

!SocksSocket methodsFor: 'initialize' stamp: 'mir 3/6/2000 13:24'!
socks5
	vers _ 5.
	method _ self noAutorizationMethod! !

!SocksSocket methodsFor: 'connection open/close' stamp: 'mir 3/6/2000 14:48'!
connectTo: hostAddress port: port
	super connectTo: socksIP port: socksPort.
	self waitForConnectionUntil: Socket standardDeadline.
	dstIP _ hostAddress.
	dstPort _ port.
	vers == 4
		ifTrue: [self connectSocks4]
		ifFalse: [self connectSocks5]
	! !

!SocksSocket methodsFor: 'connection open/close' stamp: 'mir 3/6/2000 15:17'!
connectToHostNamed: hostName port: port
	super connectTo: socksIP port: socksPort.
	self waitForConnectionUntil: Socket standardDeadline.
	dstName _ hostName.
	dstPort _ port.
	vers == 4
		ifTrue: [self connectSocks4]
		ifFalse: [self connectSocks5]
	! !


!SocksSocket class methodsFor: 'class initialization' stamp: 'mir 3/7/2000 12:59'!
initialize
	"SocksSocket initialize"

	DefaultSocksHostName _ HTTPSocket proxyServer.
	DefaultSocksPort _ 1080! !

!SocksSocket reorganize!
('methods' noAutorizationMethod)
('private' connectCommandCode defaultSocksHostAddress defaultSocksPort defaultTimeOutDuration dstIP requestGrantedCode socksError: waitForReply:for:)
('socks5' connectSocks5 hostIP6Code hostIPCode qualifiedHostNameCode sendSocks5ConnectionRequest skipQualifiedHostName socks5MethodSelection socks5RequestReply)
('socks4' connectSocks4 sendSocks4ConnectionRequestUserId: waitForSocks4ConnectionReply)
('initialize' initialize: socks4 socks5)
('connection open/close' connectTo:port: connectToHostNamed:port:)
('sending-receiving')
!


SocksSocket initialize!


More information about the Squeak-dev mailing list