[Newbies] SocketStream

Göran Krampe goran at krampe.se
Thu Sep 25 13:15:57 UTC 2008


Hey!

Rob Rothwell wrote:
> If I just want a simple "server" that listens for a text message on a port,
> does something, and sends back a text message, do I just need to somehow:
> 1.  Create a Socket and listen on the port.
> 2.  Create a SocketStream on: theSocket.
> 3.  Somehow fork and wait for input, reading it in using the SocketStream?
> 
> I just want to make sure I am on the right track while trying to find the
> magic incantation...

Yes, you are on the right track. I am working on something called
Blackfoot that is meant to be a nice, clean and simple server for SCGI.

I am attaching BFListener from Blackfoot - just change
#serveConnectionOn: to do something different inside the block there.

BFListener is a simplified derivation from TcpServices (on SqueakMap)
that KomHttpServer uses and WAListener from Seaside - yet another
alternative.

regards, Göran
-------------- next part --------------
'From Squeak3.9 of 7 November 2006 [latest update: #7067] on 25 September 2008 at 3:14:35 pm'!
Object subclass: #BFListener
	instanceVariableNames: 'port process block'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Blackfoot'!
!BFListener commentStamp: 'gk 9/25/2008 15:13' prior: 0!
Blackfoot is a minimalistic rewrite of KomHttpServer that is meant to be used with SCGI together with a fast external webserver as Nginx, Cherokee, Lighttpd or Apache that supports SCGI.

Only the necessary code has been borrowed and cleaned from KomHttpServer - lots of extra stuff has been left out. We also do not utilize DynamicBindings for "call stack scoped values" but instead use the borrowed DynamicVariable class from Seaside called BFDynamicVariable.

This class doubles as HttpService and HttpAdaptor from KomHttpServer to make it all simpler - we do not anticipate any other adaptor. This class is also a good example of a "generic forking Socket server".!


!BFListener methodsFor: 'override in subclass' stamp: 'gk 9/9/2008 23:07'!
readRequest: stream

	^BFHttpRequest readFrom: stream! !

!BFListener methodsFor: 'override in subclass' stamp: 'gk 9/9/2008 22:17'!
writeResponse: response on: stream
	response ifNil: [ ^ self ].
"	response class = WAResponse
		ifTrue: [ aStream resetBuffers ]."
	response writeOn: stream.
	response release! !


!BFListener methodsFor: 'private' stamp: 'gk 9/9/2008 21:45'!
listenLoop
	"We create a listening Socket, then wait for a connection.
	After each connection we also check that the listening Socket
	is still valid - if not we just make a recursive call to this method
	to start over."

	| socket |
	socket := Socket newTCP.
	socket listenOn: port backlogSize: self backlogSize.
	socket isValid
		ifFalse: [ self error: 'Cannot create socket on port ', port displayString ].
	[[
		socket isValid ifFalse: [
			"will trigger #ifCurtailed: block and destroy socket"
			^self listenLoop ].
		self serveConnectionOn: socket] repeat ]
	
		ifCurtailed: [
			"probably copy pasted from ConnectionQueue >> #listenLoop"
			(Delay forMilliseconds: 10) wait.
			socket destroy ]! !

!BFListener methodsFor: 'private' stamp: 'gk 9/9/2008 22:13'!
serveConnectionOn: listeningSocket
	"We wait up to 10 seconds for an incoming connection.
	If we get one we wrap it in a SocketStream and then
	we process it in three steps:
		1. Call #readRequest: to get a request object.
		2. Let the serve block handle the request and return a response object.
		3. Call #writeResponse:on: to write the response object on the stream."
		 
	| stream socket |
	socket := (listeningSocket waitForAcceptFor: 10) ifNil: [^ self].
	stream := SocketStream on: socket.
	stream autoFlush: true.
	
	[[[self writeResponse: (block value: (self readRequest: stream)) on: stream]
		ensure: [ stream close ]]
			ifCurtailed: [ socket destroy ]]
				forkAt: self servePriority! !


!BFListener methodsFor: 'accessing' stamp: 'gk 9/3/2008 18:09'!
block
	^block! !

!BFListener methodsFor: 'accessing' stamp: 'gk 9/11/2008 00:00'!
block: anObject
	block := anObject! !

!BFListener methodsFor: 'accessing' stamp: 'gk 9/9/2008 21:22'!
port
	  ^port! !

!BFListener methodsFor: 'accessing' stamp: 'gk 9/3/2008 18:09'!
port: aNumber
	port := aNumber! !


!BFListener methodsFor: 'constants' stamp: 'gk 9/9/2008 21:47'!
backlogSize
	^50! !

!BFListener methodsFor: 'constants' stamp: 'gk 9/11/2008 01:01'!
servePriority
	^Processor highIOPriority "userBackgroundPriority"! !


!BFListener methodsFor: 'public' stamp: 'gk 9/2/2008 23:53'!
start
	self stop.
	process := [ [ self listenLoop ] repeat ]
		forkAt: Processor highIOPriority! !

!BFListener methodsFor: 'public' stamp: 'gk 9/2/2008 23:53'!
stop
	process ifNotNil: [process terminate. process := nil]! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

BFListener class
	instanceVariableNames: 'Default'!

!BFListener class methodsFor: 'accessing' stamp: 'gk 9/3/2008 18:06'!
default
	^ Default! !


!BFListener class methodsFor: 'initialization' stamp: 'gk 9/2/2008 23:53'!
initialize
	Smalltalk addToStartUpList: self after: AutoStart.
	Smalltalk addToShutDownList: self! !

!BFListener class methodsFor: 'initialization' stamp: 'gk 9/3/2008 18:07'!
shutDown
	Default ifNotNil: [ Default stop ]! !

!BFListener class methodsFor: 'initialization' stamp: 'gk 9/3/2008 18:07'!
startUp
	Default ifNotNil: [ Default start ]! !


!BFListener class methodsFor: 'public' stamp: 'gk 9/10/2008 23:06'!
startDefaultOn: aNumber block: aBlock
	Default ifNotNil: [ Default stop ].
	^Default := self startOn: aNumber block: aBlock! !

!BFListener class methodsFor: 'public' stamp: 'gk 9/10/2008 00:25'!
startOn: aNumber block: aBlock
	^self new port: aNumber; block: aBlock; start! !

!BFListener class methodsFor: 'public' stamp: 'gk 9/9/2008 21:31'!
stop
	Default ifNotNil: [ Default stop ].
	Default := nil! !


BFListener initialize!


More information about the Beginners mailing list