Squeak 2.2 and firewalls

Michael S. Klein mklein at alumni.caltech.edu
Thu Sep 17 00:44:26 UTC 1998


On Thu, 17 Sep 1998, Eric Ulevik wrote:

> With Squeak now including a web browser, it would be good if it was =
> fixed to work through http firewalls. Currently, it just errors on =
> resolving server names.
>
> 1) Anyone working on this? 2) If not, any hints as to where to start?

See:

	HTTPSocket >># useProxyServerNamed:port:

Unfortunately there is a bug if your proxy server is not on port 80.
Fortunately I have included the fix.

-- Mike Klein

P.S.  Please dont send HTML mail to the squeak-list

'From Squeak 2.2beta of Sept 16, 1998 on 16 September 1998 at 5:25:04 pm'!

!HTTPSocket commentStamp: 'msk 9/16/1998 16:16' prior: 0!
HTTPSockets support HTTP requests, either directly or via an HTTP proxy server. An HTTPSocket saves the parse of the last ASCII header it saw, to avoid having to parse it repeatedly.

The real action is in httpGet:accept:.  See the examples in the class, especially httpFileInNewChangeSet: and httpShowGif:.

Class Variables:
	HTTPProxy	<String>	The proxy server's name
	HTTPPort	<Integer | nil>	The proxy server's port
	HTTPBlabEmail	<String>	An optional request header, tentatively to inform the server of your email address.!
]style[(206 15 45 23 5 15 218)f1,f1LHTTPSocket class httpGet:accept:;,f1,f1LHTTPSocket class httpFileInNewChangeSet:;,f1,f1LHTTPSocket class httpShowGif:;,f1!

!HTTPSocket class methodsFor: 'class initialization' stamp: 'msk 9/16/1998 16:09'!
initialize
	"HTTPSocket initialize"

	ParamDelimiters _ ' ', CrLf.
	HTTPPort _ nil.
	HTTPProxy _ nil.
	HTTPBlabEmail _ ''.  "	'From: tedk at disney.com', CrLf	"
! !

!HTTPSocket class methodsFor: 'examples' stamp: 'msk 9/16/1998 16:09'!
httpGetDocument: url args: args accept: mimeType
	"Return the exact contents of a web object. Asks for the given MIME type. If mimeType is nil, use 'text/html'. The parsed header is saved. Use a proxy server if one has been registered.  tk 7/23/97 17:12"
	"Note: To fetch raw data, you can use the MIME type 'application/octet-stream'."

	| serverName serverAddr port sock header length bare page list firstData aStream index first connectToHost connectToPort type argsString newUrl |
	Socket initializeNetwork.
	bare _ (url asLowercase beginsWith: 'http://') 
		ifTrue: [url copyFrom: 8 to: url size]
		ifFalse: [url].
	bare _ bare copyUpTo: $#.  "remove fragment, if specified"
	serverName _ bare copyUpTo: $/.
	page _ bare copyFrom: serverName size + 1 to: bare size.
	(serverName includes: $:) 
		ifTrue: [ index _ serverName indexOf: $:.
			port _ (serverName copyFrom: index+1 to: serverName size) asNumber.
			serverName _ serverName copyFrom: 1 to: index-1. ]
		ifFalse: [ port _ self defaultPort ].
	page size = 0 ifTrue: [page _ '/'].
	"add arguments"
	args ifNotNil: [
		argsString _ WriteStream on: String new.
		argsString nextPut: $?.
		first _ true.
		args associationsDo: [ :assoc |
			assoc value do: [ :value |
				first ifTrue: [ first _ false ] ifFalse: [ argsString nextPut: $& ].
				argsString nextPutAll: assoc key encodeForHTTP.
				argsString nextPut: $=.
				argsString nextPutAll: value encodeForHTTP. ] ].
		argsString _ argsString contents.
		page _ page, argsString ].


	HTTPProxy isNil
		ifTrue: [ 
			connectToHost _ serverName.
			connectToPort _ port ]
		ifFalse:  [
			page _ 'http://', serverName, ':', port printString, page.		"put back together"
			connectToHost _ HTTPProxy.
			connectToPort _ HTTPPort].
	
	self flag: #XXX.  "this doesn't make sense if a user isn't available for questioning...  -ls"
	self retry: [serverAddr _ NetNameResolver addressForName: connectToHost timeout: 20.
				serverAddr ~~ nil] 
		asking: 'Trouble resolving server name.  Keep trying?'
		ifGiveUp: [Socket deadServer: connectToHost.
				^ 'Could not resolve the server named: ', connectToHost].

	sock _ HTTPSocket new.
	sock connectTo: serverAddr port: connectToPort.
	(sock waitForConnectionUntil: (self deadlineSecs: 30)) ifFalse: [
		Socket deadServer: connectToHost.  sock destroy.
		^ 'Server ',connectToHost,' is not responding'].
	Transcript cr; show: connectToHost; cr.
	sock sendCommand: 'GET ', page, ' HTTP/1.0', CrLf, 
		(mimeType ifNotNil: ['ACCEPT: ', mimeType, CrLf] ifNil: ['']),
		'ACCEPT: text/html', CrLf,	"Always accept plain text"
		HTTPBlabEmail,	"may be empty"
		'User-Agent: Squeak 1.31', CrLf,
		'Host: ', serverName, ':', port printString, CrLf.	"blank line automatically added"

	list _ sock getResponseUpTo: CrLf, CrLf.	"list = header, CrLf, CrLf, beginningOfData"
	header _ list at: 1.
	Transcript show: page; cr; show: header; cr.
	firstData _ list at: 3.

	header isEmpty ifTrue: [ ^'no header' ].

	"dig out some headers"
	sock header: header.
	length _ sock getHeader: 'content-length'.
	length ifNotNil: [ length _ length asNumber ].
	type _ sock getHeader: 'content-type'.
	sock responseCode first = $3 ifTrue: [
		newUrl _ sock getHeader: 'location'.
		newUrl ifNotNil: [ 
			Transcript show: 'redirecting to ', newUrl; cr.
			sock destroy.
			^self httpGetDocument: newUrl  args: args  accept: mimeType ] ].

	aStream _ sock getRestOfBuffer: firstData totalLength: length.
	sock destroy.	"Always OK to destroy!!"

 	^ MIMEDocument contentType: type content: aStream contents url: url! !

!HTTPSocket class methodsFor: 'constants' stamp: 'msk 9/16/1998 16:04'!
defaultPort
	^80! !


HTTPSocket initialize!





More information about the Squeak-dev mailing list