[squeak-dev] The Inbox: Network-ul.100.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Dec 12 04:12:47 UTC 2010


A new version of Network was added to project The Inbox:
http://source.squeak.org/inbox/Network-ul.100.mcz

==================== Summary ====================

Name: Network-ul.100
Author: ul
Time: 12 December 2010, 4:49:19.894 am
UUID: 81823263-c3d6-f949-a8b0-6a107dcb5322
Ancestors: Network-ul.99

Network changes from the EToys repository.

=============== Diff against Network-ul.99 ===============

Item was changed:
  Object subclass: #ConnectionQueue
  	instanceVariableNames: 'portNumber maxQueueLength connections accessSema socket process'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Network-Kernel'!
  
  !ConnectionQueue commentStamp: '<historical>' prior: 0!
  A ConnectionQueue listens on a given port number and collects a queue of client connections. In order to handle state changes quickly, a ConnectionQueue has its own process that: (a) tries to keep a socket listening on the port whenever the queue isn't already full of connections and (b) prunes stale connections out of the queue to make room for fresh ones.
+ 
+ The portNumber can be initialized to a collection, in which case all ports will be probed to create a listening socket. Once successfull, the portNumber is set to the chosen port.!
- !

Item was added:
+ ----- Method: ConnectionQueue>>createListeningSocketWithBacklog: (in category 'private') -----
+ createListeningSocketWithBacklog: aNumber
+ 	| addressInfo sock |
+ 	self portNumbers do: [:trialportNumber | 
+ 		addressInfo := SocketAddressInformation
+ 			forHost: ''
+ 			service: trialportNumber asString
+ 			flags: SocketAddressInformation passiveFlag
+ 			addressFamily: SocketAddressInformation addressFamilyINET4
+ 			socketType: SocketAddressInformation socketTypeStream
+ 			protocol: SocketAddressInformation protocolTCP.
+ 		sock := [addressInfo first listenWithBacklog: aNumber] ifError: [nil].
+ 		sock ifNotNil: [
+ 			portNumber := trialportNumber.
+ 			^ sock]].
+ 	^ nil!

Item was changed:
  ----- Method: ConnectionQueue>>listenLoop (in category 'private') -----
  listenLoop
  	"Private!! This loop is run in a separate process. It will establish up to maxQueueLength connections on the given port."
  	"Details: When out of sockets or queue is full, retry more frequently, since a socket may become available, space may open in the queue, or a previously queued connection may be aborted by the client, making it available for a fresh connection."
  	"Note: If the machine is disconnected from the network while the server is running, the currently waiting socket will go from 'isWaitingForConnection' to 'unconnected', and attempts to create new sockets will fail. When this happens, delete the broken socket and keep trying to create a socket in case the network connection is re-established. Connecting and disconnecting was tested under PPP on Mac system 8.1. It is not if this will work on other platforms."
  
  
  	| newConnection |
- 
- 	socket := Socket newTCP.
  	"We'll accept four simultanous connections at the same time"
+ 	NetNameResolver useOldNetwork
+ 		ifFalse: [ socket := self createListeningSocketWithBacklog: 4 ]
+ 		ifTrue: [
+ 			socket := Socket newTCP.
+ 			socket listenOn: portNumber backlogSize: 4 ].
- 	socket listenOn: portNumber backlogSize: 4.
  	"If the listener is not valid then the we cannot use the
  	BSD style accept() mechanism."
  	socket isValid ifFalse: [^self oldStyleListenLoop].
  	[true] whileTrue: [
  		socket isValid ifFalse: [
  			"socket has stopped listening for some reason"
  			socket destroy.
  			(Delay forMilliseconds: 10) wait.
  			^self listenLoop ].
  		newConnection := socket 
  			waitForAcceptFor: 10
  			ifTimedOut: [ nil ].
  		(newConnection notNil and: [newConnection isConnected]) ifTrue: [
  			accessSema critical: [connections addLast: newConnection.].
  			newConnection := nil.
  			self changed].
  		self pruneStaleConnections]. !

Item was added:
+ ----- Method: ConnectionQueue>>portNumber (in category 'public') -----
+ portNumber
+ 	^ portNumber isCollection
+ 		ifTrue: [portNumber first]
+ 		ifFalse: [portNumber]!

Item was added:
+ ----- Method: ConnectionQueue>>portNumberOrNil (in category 'public') -----
+ portNumberOrNil
+ 	"Answer nil while actual port has not been established"
+ 	^ portNumber isCollection
+ 		ifFalse: [portNumber]!

Item was added:
+ ----- Method: ConnectionQueue>>portNumbers (in category 'public') -----
+ portNumbers
+ 	^ portNumber isCollection
+ 		ifTrue: [portNumber]
+ 		ifFalse: [{portNumber}]!

Item was changed:
  ----- Method: HTTPSocket class>>httpShowPage: (in category 'get the page') -----
  httpShowPage: url
  	"Display the exact contents of the given URL as text. See examples in httpGet:"
  
  	| doc |
  	doc := (self httpGet: url accept: 'application/octet-stream') contents.
+ 	doc size = 0 ifTrue: [^ self error: 'Document could not be fetched' translated].
- 	doc size = 0 ifTrue: [^ self error: 'Document could not be fetched'].
  	(StringHolder new contents: doc) openLabel: url.
  !

Item was changed:
  Object subclass: #NetNameResolver
  	instanceVariableNames: ''
+ 	classVariableNames: 'DefaultHostName HaveNetwork ResolverBusy ResolverError ResolverMutex ResolverReady ResolverSemaphore ResolverUninitialized UseOldNetwork'
- 	classVariableNames: 'DefaultHostName HaveNetwork ResolverBusy ResolverError ResolverMutex ResolverReady ResolverSemaphore ResolverUninitialized'
  	poolDictionaries: ''
  	category: 'Network-Kernel'!
  
  !NetNameResolver commentStamp: '<historical>' prior: 0!
  This class implements TCP/IP style network name lookup and translation facilities.
  
  Attempt to keep track of whether there is a network available.
  HaveNetwork	true if last attempt to contact the network was successful.
  LastContact		Time of that contact (totalSeconds).
  haveNetwork	returns true, false, or #expired.  True means there was contact in the last 30 minutes.  False means contact failed or was false last time we asked.  Get out of false state by making contact with a server in some way (FileList or updates).!

Item was changed:
  ----- Method: NetNameResolver class>>addressForName: (in category 'lookups') -----
+ addressForName: hostName
+ 	"NetNameResolver addressForName: 'impara.de' "
+ 	"NetNameResolver addressForName: 'localhost' "
+ 	"NetNameResolver addressForName: '127.0.0.1' "
+ 	| addresses |
+ 	self useOldNetwork
+ 		ifTrue: [^self oldAddressForName: hostName].
+ 	addresses := self addressesForName: hostName.
+ 	^addresses
+ 		ifEmpty: [nil]
+ 		ifNotEmpty: [addresses first socketAddress]!
- addressForName: aString
- 	^self addressForName: aString timeout: 60!

Item was changed:
  ----- Method: NetNameResolver class>>addressForName:timeout: (in category 'lookups') -----
  addressForName: hostName timeout: secs
  	"Look up the given host name and return its address. Return nil if the address is not found in the given number of seconds."
  	"NetNameResolver addressForName: 'create.ucsb.edu' timeout: 30"
  	"NetNameResolver addressForName: '100000jobs.de' timeout: 30"
  	"NetNameResolver addressForName: '1.7.6.4' timeout: 30"
  	"NetNameResolver addressForName: '' timeout: 30 (This seems to return nil?)"
  
  	| deadline result |
  	self initializeNetwork.
+ 	self useOldNetwork
+ 		ifFalse: [^self addressForName: hostName].
  	"check if this is a valid numeric host address (e.g. 1.2.3.4)"
  	result := self addressFromString: hostName.
+ 	result isNil ifFalse: [^result asSocketAddress].
- 	result isNil ifFalse: [^result].
  
  	"Look up a host name, including ones that start with a digit (e.g. 100000jobs.de or squeak.org)"
  	deadline := Time millisecondClockValue + (secs * 1000).
  	"Protect the execution of this block, as the ResolverSemaphore is used for both parts of the transaction."
  	self resolverMutex
  		critical: [
  			(self waitForResolverReadyUntil: deadline)
  				ifTrue: [
  					self primStartLookupOfName: hostName.
  					(self waitForCompletionUntil: deadline)
  						ifTrue: [result := self primNameLookupResult]
  						ifFalse: [(NameLookupFailure hostName: hostName) signal: 'Could not resolve the server named: ', hostName]]
  				ifFalse: [(NameLookupFailure hostName: hostName) signal: 'Could not resolve the server named: ', hostName]].
+ 	^result asSocketAddress!
- 	^result!

Item was added:
+ ----- Method: NetNameResolver class>>addressesForName: (in category 'lookup') -----
+ addressesForName: hostName
+ 	"NetNameResolver addressesForName: 'impara.de' "
+ 	
+ 	| addresses |
+ 	addresses := SocketAddressInformation
+ 		forHost: hostName
+ 		service: ''
+ 		flags: 0
+ 		addressFamily: 0
+ 		socketType: SocketAddressInformation socketTypeStream
+ 		protocol: SocketAddressInformation protocolTCP.
+ 	^addresses!

Item was changed:
  ----- Method: NetNameResolver class>>initializeNetwork (in category 'network initialization') -----
  initializeNetwork
  	"Initialize the network drivers and record the semaphore to be used by the resolver. Do nothing if the network is already initialized. Evaluate the given block if network initialization fails."
+ 	"NetNameResolver initializeNetwork" 
- 	"NetNameResolver initializeNetwork"
  
  	| semaIndex |
  	self resolverStatus = ResolverUninitialized
  		ifFalse: [^HaveNetwork := true].  "network is already initialized"
  
  	HaveNetwork := false.	"in case abort"
  	ResolverSemaphore := Semaphore new.
  	semaIndex := Smalltalk registerExternalObject: ResolverSemaphore.
  
  	"result is nil if network initialization failed, self if it succeeds"
  	(self primInitializeNetwork: semaIndex)
  		ifNil: [NoNetworkError signal: 'failed network initialization']
  		ifNotNil: [HaveNetwork := true].
+ 
+ 	UseOldNetwork := [NetNameResolver primHostNameSize. false]
+ 		on: Error
+ 		do: [:ex | ex return: true]
  !

Item was changed:
  ----- Method: NetNameResolver class>>localAddressString (in category 'lookups') -----
  localAddressString
  	"Return a string representing the local host address as four decimal bytes delimited with decimal points."
  	"NetNameResolver localAddressString"
  
+ 	self useOldNetwork
+ 		ifTrue: [^self stringFromAddress: self primLocalAddress].
+ 	^self localHostAddress hostNumber!
- 	^ NetNameResolver stringFromAddress: NetNameResolver localHostAddress
- !

Item was changed:
  ----- Method: NetNameResolver class>>localHostAddress (in category 'lookups') -----
  localHostAddress
  	"Return the local address of this host."
  	"NetNameResolver localHostAddress"
  
+ 	self useOldNetwork ifTrue: [
+ 		self initializeNetwork.
+ 		^self primLocalAddress ].
+ 	^NetNameResolver addressForName: self localHostName!
- 	self initializeNetwork.
- 	^ self primLocalAddress
- !

Item was changed:
  ----- Method: NetNameResolver class>>localHostName (in category 'lookups') -----
  localHostName
  	"Return the local name of this host."
  	"NetNameResolver localHostName"
  
+ 	| host |
+ 	self useOldNetwork ifTrue: [
+ 		| hostName |
+ 		hostName := self
+ 			nameForAddress: self localHostAddress
+ 			timeout: 5.
+ 		^hostName ifNil: [ self localAddressString ] ].
+ 	host := String new: NetNameResolver primHostNameSize.
+ 	NetNameResolver primHostNameResult: host.
+ 	^host!
- 	| hostName |
- 	hostName := NetNameResolver
- 		nameForAddress: self localHostAddress
- 		timeout: 5.
- 	^hostName
- 		ifNil: [self localAddressString]
- 		ifNotNil: [hostName]!

Item was added:
+ ----- Method: NetNameResolver class>>nextSocketAddressInformation (in category 'private') -----
+ nextSocketAddressInformation
+ 
+ 	| addrSize addr info |
+ 	addrSize := self primGetAddressInfoSize.
+ 	addrSize < 0 ifTrue: [^nil].
+ 	addr := SocketAddress new: addrSize.
+ 	self primGetAddressInfoResult: addr.
+ 	info := SocketAddressInformation
+ 		withSocketAddress: addr
+ 		family: self primGetAddressInfoFamily
+ 		type: self primGetAddressInfoType
+ 		protocol: self primGetAddressInfoProtocol.
+ 	self primGetAddressInfoNext.
+ 	^info!

Item was added:
+ ----- Method: NetNameResolver class>>oldAddressForName: (in category 'lookups-old') -----
+ oldAddressForName: aString
+ 	"NetNameResolver oldAddressForName: 'vpri.org' "
+ 	^self addressForName: aString timeout: 60!

Item was added:
+ ----- Method: NetNameResolver class>>primGetAddressInfoFamily (in category 'primitives-ipv6') -----
+ primGetAddressInfoFamily
+ 
+ 	<primitive: 'primitiveResolverGetAddressInfoFamily' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was added:
+ ----- Method: NetNameResolver class>>primGetAddressInfoHost:service:flags:family:type:protocol: (in category 'primitives-ipv6') -----
+ primGetAddressInfoHost: hostName service: servName flags: flags family: family type: type protocol: protocol
+ 
+ 	<primitive: 'primitiveResolverGetAddressInfo' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was added:
+ ----- Method: NetNameResolver class>>primGetAddressInfoNext (in category 'primitives-ipv6') -----
+ primGetAddressInfoNext
+ 
+ 	<primitive: 'primitiveResolverGetAddressInfoNext' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was added:
+ ----- Method: NetNameResolver class>>primGetAddressInfoProtocol (in category 'primitives-ipv6') -----
+ primGetAddressInfoProtocol
+ 
+ 	<primitive: 'primitiveResolverGetAddressInfoProtocol' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was added:
+ ----- Method: NetNameResolver class>>primGetAddressInfoResult: (in category 'primitives-ipv6') -----
+ primGetAddressInfoResult: socketAddress
+ 
+ 	<primitive: 'primitiveResolverGetAddressInfoResult' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was added:
+ ----- Method: NetNameResolver class>>primGetAddressInfoSize (in category 'primitives-ipv6') -----
+ primGetAddressInfoSize
+ 
+ 	<primitive: 'primitiveResolverGetAddressInfoSize' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was added:
+ ----- Method: NetNameResolver class>>primGetAddressInfoType (in category 'primitives-ipv6') -----
+ primGetAddressInfoType
+ 
+ 	<primitive: 'primitiveResolverGetAddressInfoType' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was added:
+ ----- Method: NetNameResolver class>>primGetNameInfo:flags: (in category 'primitives-ipv6') -----
+ primGetNameInfo: socketAddress flags: flags
+ 
+ 	<primitive: 'primitiveResolverGetNameInfo' module: 'SocketPlugin'>
+ 	flags == 0 ifTrue: [^self primGetNameInfo: socketAddress
+ 						flags: SocketAddressInformation numericFlag].
+ 	self primitiveFailed!

Item was added:
+ ----- Method: NetNameResolver class>>primGetNameInfoHostResult: (in category 'primitives-ipv6') -----
+ primGetNameInfoHostResult: aString
+ 
+ 	<primitive: 'primitiveResolverGetNameInfoHostResult' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was added:
+ ----- Method: NetNameResolver class>>primGetNameInfoHostSize (in category 'primitives-ipv6') -----
+ primGetNameInfoHostSize
+ 
+ 	<primitive: 'primitiveResolverGetNameInfoHostSize' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was added:
+ ----- Method: NetNameResolver class>>primGetNameInfoServiceResult: (in category 'primitives-ipv6') -----
+ primGetNameInfoServiceResult: aString
+ 
+ 	<primitive: 'primitiveResolverGetNameInfoServiceResult' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was added:
+ ----- Method: NetNameResolver class>>primGetNameInfoServiceSize (in category 'primitives-ipv6') -----
+ primGetNameInfoServiceSize
+ 
+ 	<primitive: 'primitiveResolverGetNameInfoServiceSize' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was added:
+ ----- Method: NetNameResolver class>>primHostNameResult: (in category 'primitives-ipv6') -----
+ primHostNameResult: aString
+ 
+ 	<primitive: 'primitiveResolverHostNameResult' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was added:
+ ----- Method: NetNameResolver class>>primHostNameSize (in category 'primitives-ipv6') -----
+ primHostNameSize
+ 
+ 	<primitive: 'primitiveResolverHostNameSize' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was added:
+ ----- Method: NetNameResolver class>>testIPv6 (in category 'tests') -----
+ testIPv6
+ 	"NetNameResolver testIPv6"
+ 	| infos addr sock size host serverSocket listeningSocket clientSocket |
+ 	World findATranscript: World currentEvent.
+ 	Transcript clear.
+ 	"Transcript show: SmalltalkImage current listLoadedModules; cr."
+ 	self initializeNetwork.
+ 	Transcript show: '---- host name ----'; cr.
+ 	size := NetNameResolver primHostNameSize.
+ 	host := String new: size.
+ 	NetNameResolver primHostNameResult: host.
+ 	Transcript show: host; cr.
+ 	Transcript show: '---- address information ----'; cr.
+ 	Transcript show: (infos := SocketAddressInformation
+ 						forHost: 'localhost' service: 'echo' flags: 0
+ 						addressFamily: 0 socketType: 0 protocol: 0) printString; cr.
+ 	Transcript show: '---- port manipulation ----'; cr.
+ 	addr := infos first socketAddress.
+ 	Transcript show: addr port printString; cr.
+ 	addr port: 1234.
+ 	Transcript show: addr port printString; cr.
+ 	Transcript show: addr printString; cr.
+ 	Transcript show: '---- client socket ----'; cr.
+ 	Transcript show: (infos := SocketAddressInformation
+ 						forHost: 'localhost' service: 'echo' flags: 0
+ 						addressFamily: 0
+ 						socketType: SocketAddressInformation socketTypeStream
+ 						protocol: SocketAddressInformation protocolTCP) printString; cr.
+ 	infos do: [:info |
+ 		Transcript show: 'Trying ', info printString, '... '.
+ 		(sock := info connect) notNil
+ 			ifTrue:
+ 				[sock sendData: 'hello' count: 5.
+ 				 Transcript show: sock receiveData printString.
+ 				 sock close; destroy].
+ 		Transcript cr].
+ 	Transcript show: '---- localhost defaults: loopback and wildcard addresses ----'; cr.
+ 	Transcript show: (SocketAddress loopbacks) printString; cr.
+ 	Transcript show: (SocketAddress wildcards) printString; cr.
+ 	Transcript show: (SocketAddress loopback4) printString; cr.
+ 	Transcript show: (SocketAddress wildcard4) printString; cr.
+ 	Transcript show: '---- impossible constraints ----'; cr.
+ 	Transcript show: (SocketAddressInformation
+ 						forHost: 'localhost' service: 'echo' flags: 0
+ 						addressFamily:	0
+ 						socketType:		SocketAddressInformation socketTypeDGram
+ 						protocol:		SocketAddressInformation protocolTCP) printString; cr.
+ 	Transcript show: '---- INET4 client-server ----'; cr.
+ 	Transcript show: (infos := SocketAddressInformation
+ 						forHost: '' service: '4242'
+ 						flags:			SocketAddressInformation passiveFlag
+ 						addressFamily:	SocketAddressInformation addressFamilyINET4
+ 						socketType:		SocketAddressInformation socketTypeStream
+ 						protocol:		SocketAddressInformation protocolTCP) printString; cr.
+ 	listeningSocket := infos first listenWithBacklog: 5.
+ 	Transcript show: (infos := SocketAddressInformation
+ 						forHost: 'localhost' service: '4242'
+ 						flags:			0
+ 						addressFamily:	SocketAddressInformation addressFamilyINET4
+ 						socketType:		SocketAddressInformation socketTypeStream
+ 						protocol:		SocketAddressInformation protocolTCP) printString; cr.
+ 	clientSocket := infos first connect.
+ 	serverSocket := listeningSocket accept.
+ 	serverSocket sendData: 'Hi there!!' count: 9.
+ 	Transcript show: clientSocket receiveData; cr.
+ 	Transcript nextPutAll: 'client side local/remote: ';
+ 		print: clientSocket localSocketAddress; space;
+ 		print: clientSocket remoteSocketAddress; cr.
+ 	Transcript nextPutAll: 'server side local/remote: ';
+ 		print: serverSocket localSocketAddress; space;
+ 		print: serverSocket remoteSocketAddress; cr;
+ 		endEntry.
+ 	clientSocket close; destroy.
+ 	serverSocket close; destroy.
+ 	listeningSocket close; destroy.
+ 	Transcript show: '---- INET6 client-server ----'; cr.
+ 	Transcript show: (infos := SocketAddressInformation
+ 						forHost: '' service: '4242'
+ 						flags:			SocketAddressInformation passiveFlag
+ 						addressFamily:	SocketAddressInformation addressFamilyINET6
+ 						socketType:		SocketAddressInformation socketTypeStream
+ 						protocol:		SocketAddressInformation protocolTCP) printString; cr.
+ 	infos isEmpty
+ 		ifTrue: [Transcript show: 'FAIL -- CANNOT CREATE INET6 SERVER'; cr]
+ 		ifFalse:
+ 			[listeningSocket := infos first listenWithBacklog: 5.
+ 			Transcript show: (infos := SocketAddressInformation
+ 								forHost: 'localhost' service: '4242'
+ 								flags:			0
+ 								addressFamily:	SocketAddressInformation addressFamilyINET6
+ 								socketType:		SocketAddressInformation socketTypeStream
+ 								protocol:		SocketAddressInformation protocolTCP) printString; cr.
+ 			clientSocket := infos first connect.
+ 			serverSocket := listeningSocket accept.
+ 			serverSocket sendData: 'Hi there!!' count: 9.
+ 			Transcript show: clientSocket receiveData; cr.
+ 			Transcript nextPutAll: 'client side local/remote: ';
+ 				print: clientSocket localSocketAddress; space;
+ 				print: clientSocket remoteSocketAddress; cr.
+ 			Transcript nextPutAll: 'server side local/remote: ';
+ 				print: serverSocket localSocketAddress; space;
+ 				print: serverSocket remoteSocketAddress; cr;
+ 				endEntry.
+ 			clientSocket close; destroy.
+ 			serverSocket close; destroy.
+ 			listeningSocket close; destroy].
+ 	Transcript show: '---- trivial tests done ---'; cr.!

Item was added:
+ ----- Method: NetNameResolver class>>testPort80 (in category 'tests') -----
+ testPort80
+ 	"NetNameResolver testPort80"
+ 	| infos |
+ 	Transcript show: (infos := SocketAddressInformation
+ 						forHost: 'localhost' service: '80' flags: 0
+ 						addressFamily: 0 socketType: 0 protocol: 0) printString; cr.
+ 	Transcript show: (infos := SocketAddressInformation
+ 						forHost: '::1' service: '80' flags: 0
+ 						addressFamily: 0 socketType: 0 protocol: 0) printString; cr.
+ !

Item was added:
+ ----- Method: NetNameResolver class>>useOldNetwork (in category 'private') -----
+ useOldNetwork
+ 	^UseOldNetwork ~~ false!

Item was added:
+ ----- Method: SMTPClient class>>openOnHost:port: (in category 'instance creation') -----
+ openOnHost: hostIP port: portNumber
+ 
+ 	| client |
+ 	client := super openOnHost: hostIP port: portNumber.
+ 	client initiateSession.
+ 	^client!

Item was changed:
  ----- Method: Socket class>>newTCP (in category 'instance creation') -----
  newTCP
  	"Create a socket and initialise it for TCP"
+ 	^self newTCP: SocketAddressInformation addressFamilyINET4!
- 	self initializeNetwork.
- 	^[ super new initialize: TCPSocketType ]
- 		repeatWithGCIf: [ :socket | socket isValid not ]!

Item was added:
+ ----- Method: Socket class>>newTCP: (in category 'instance creation') -----
+ newTCP: family
+ 	"Create a socket and initialise it for TCP"
+ 	self initializeNetwork.
+ 	^[ super new initialize: TCPSocketType family: family ]
+ 		repeatWithGCIf: [ :socket | socket isValid not ]!

Item was changed:
  ----- Method: Socket class>>newUDP (in category 'instance creation') -----
  newUDP
  	"Create a socket and initialise it for UDP"
+ 	^self newUDP: SocketAddressInformation addressFamilyINET4!
- 	self initializeNetwork.
- 	^[ super new initialize: UDPSocketType ]
- 		repeatWithGCIf: [ :socket | socket isValid not ]!

Item was added:
+ ----- Method: Socket class>>newUDP: (in category 'instance creation') -----
+ newUDP: family
+ 	"Create a socket and initialise it for UDP"
+ 	self initializeNetwork.
+ 	^[ super new initialize: UDPSocketType family: family ]
+ 		repeatWithGCIf: [ :socket | socket isValid not ]!

Item was changed:
  ----- Method: Socket class>>tcpCreateIfFail: (in category 'instance creation') -----
  tcpCreateIfFail: failBlock
  	"Attempt to create a new socket. If successful, return the new socket. Otherwise, return the result of evaluating the given block. Socket creation can fail if the network isn't available or if there are not sufficient resources available to create another socket."
  
  	| sock |
  	self initializeNetwork.
+ 	sock := self newTCP.
- 	sock := super new initialize: TCPSocketType.
  	sock isValid ifFalse: [^ failBlock value].
  	^ sock
  !

Item was added:
+ ----- Method: Socket class>>timeTest (in category 'examples') -----
+ timeTest
+ 	"Socket timeTest"
+ 
+ 	| serverName serverAddr s |
+ 	Transcript show: 'initializing network ... '.
+ 	self initializeNetwork.
+ 	Transcript
+ 		show: 'ok';
+ 		cr.
+ 	serverName := UIManager default request: 'What is your time server?'
+ 				initialAnswer: 'localhost'.
+ 	serverName isEmpty 
+ 		ifTrue: 
+ 			[^Transcript
+ 				show: 'never mind';
+ 				cr].
+ 	serverAddr := NetNameResolver addressForName: serverName timeout: 10.
+ 	serverAddr = nil 
+ 		ifTrue: [self error: 'Could not find the address for ' , serverName].
+ 	s := self new.
+ 	Transcript
+ 		show: '---------- Connecting ----------';
+ 		cr.
+ 	s connectTo: serverAddr port: 13.	"13 is the 'daytime' port number"
+ 	s waitForConnectionUntil: (self deadlineSecs: 1).
+ 	Transcript show: 'the time server reports: ' , s receiveData.
+ 	s closeAndDestroy.
+ 	Transcript
+ 		show: '---------- Connection Closed ----------';
+ 		cr!

Item was added:
+ ----- Method: Socket class>>timeTestUDP (in category 'examples') -----
+ timeTestUDP
+ 	"Socket timeTestUDP"
+ 
+ 	| serverName serverAddr s |
+ 	Transcript show: 'initializing network ... '.
+ 	self initializeNetwork.
+ 	Transcript
+ 		show: 'ok';
+ 		cr.
+ 	serverName := UIManager default request: 'What is your time server?'
+ 				initialAnswer: 'localhost'.
+ 	serverName isEmpty 
+ 		ifTrue: 
+ 			[^Transcript
+ 				show: 'never mind';
+ 				cr].
+ 	serverAddr := NetNameResolver addressForName: serverName timeout: 10.
+ 	serverAddr = nil 
+ 		ifTrue: [self error: 'Could not find the address for ' , serverName].
+ 	s := self newUDP.	"a 'random' port number will be allocated by the system"
+ 	"Send a packet to the daytime port and it will reply with the current date."
+ 	Transcript
+ 		show: '---------- Sending datagram from port ' , s port printString 
+ 					, ' ----------';
+ 		cr.
+ 	s 
+ 		sendData: '!!'
+ 		toHost: serverAddr
+ 		port: 13.	"13 is the daytime service"
+ 	Transcript show: 'the time server reports: ' , s receiveData.
+ 	s closeAndDestroy.
+ 	Transcript
+ 		show: '---------- Socket closed ----------';
+ 		cr!

Item was changed:
  ----- Method: Socket class>>udpCreateIfFail: (in category 'instance creation') -----
  udpCreateIfFail: failBlock
  	"Attempt to create a new socket. If successful, return the new socket. Otherwise, return the result of evaluating the given block. Socket creation can fail if the network isn't available or if there are not sufficient resources available to create another socket."
  
  	| sock |
  	self initializeNetwork.
+ 	sock := self newUDP.
- 	sock := super new initialize: UDPSocketType.
  	sock isValid ifFalse: [^ failBlock value].
  	^ sock
  !

Item was added:
+ ----- Method: Socket>>bindTo: (in category 'ipv6') -----
+ bindTo: aSocketAddress
+ 
+ 	| status |
+ 	self initializeNetwork.
+ 	status := self primSocketConnectionStatus: socketHandle.
+ 	(status == Unconnected)
+ 		ifFalse: [InvalidSocketStatusException signal: 'Socket status must Unconnected when binding it to an address'].
+ 
+ 	self primSocket: socketHandle bindTo: aSocketAddress.
+ !

Item was added:
+ ----- Method: Socket>>connectNonBlockingTo: (in category 'ipv6') -----
+ connectNonBlockingTo: aSocketAddress
+ 
+ 	| status |
+ 	self initializeNetwork.
+ 	status := self primSocketConnectionStatus: socketHandle.
+ 	(status == Unconnected)
+ 		ifFalse: [InvalidSocketStatusException signal: 'Socket status must Unconnected before opening a new connection'].
+ 
+ 	self primSocket: socketHandle connectTo: aSocketAddress.
+ !

Item was changed:
  ----- Method: Socket>>connectNonBlockingTo:port: (in category 'connection open/close') -----
  connectNonBlockingTo: hostAddress port: port
  	"Initiate a connection to the given port at the given host address. This operation will return immediately; follow it with waitForConnectionUntil: to wait until the connection is established."
  
  	| status |
  	self initializeNetwork.
  	status := self primSocketConnectionStatus: socketHandle.
  	(status == Unconnected)
  		ifFalse: [InvalidSocketStatusException signal: 'Socket status must Unconnected before opening a new connection'].
  
+ 	NetNameResolver useOldNetwork
+ 		ifTrue: [self primSocket: socketHandle connectTo: hostAddress port: port]
+ 		ifFalse: [
+ 			hostAddress port: port.
+ 			self connectNonBlockingTo: hostAddress]!
- 	self primSocket: socketHandle connectTo: hostAddress port: port.
- !

Item was added:
+ ----- Method: Socket>>connectTo: (in category 'ipv6') -----
+ connectTo: aSocketAddress
+ 
+ 	self connectTo: aSocketAddress waitForConnectionFor: Socket standardTimeout!

Item was changed:
  ----- Method: Socket>>connectTo:port: (in category 'connection open/close') -----
  connectTo: hostAddress port: port
  	"Initiate a connection to the given port at the given host address.
  	Waits until the connection is established or time outs."
  
+ 	NetNameResolver useOldNetwork
+ 		ifTrue: [self connectTo: hostAddress port: port waitForConnectionFor: Socket standardTimeout]
+ 		ifFalse: [
+ 			hostAddress port: port.
+ 			self connectTo: hostAddress]!
- 	self connectTo: hostAddress port: port waitForConnectionFor: Socket standardTimeout!

Item was changed:
  ----- Method: Socket>>connectTo:port:waitForConnectionFor: (in category 'connection open/close') -----
  connectTo: hostAddress port: port waitForConnectionFor: timeout 
  	"Initiate a connection to the given port at the given host 
  	address. Waits until the connection is established or time outs."
  	self connectNonBlockingTo: hostAddress port: port.
  	self
  		waitForConnectionFor: timeout
  		ifTimedOut: [ConnectionTimedOut signal: 'Cannot connect to '
+ 					, self remoteSocketAddress hostNumber , ':' , port asString]!
- 					, (NetNameResolver stringFromAddress: hostAddress) , ':' , port asString]!

Item was added:
+ ----- Method: Socket>>connectTo:waitForConnectionFor: (in category 'ipv6') -----
+ connectTo: aSocketAddress waitForConnectionFor: timeout 
+ 
+ 	self connectNonBlockingTo: aSocketAddress.
+ 	self
+ 		waitForConnectionFor: timeout
+ 		ifTimedOut: [ConnectionTimedOut signal: 'Cannot connect to ', aSocketAddress printString]!

Item was changed:
  ----- Method: Socket>>discardReceivedData (in category 'receiving') -----
  discardReceivedData
  	"Discard any data received up until now, and return the number of bytes discarded."
  
  	| buf totalBytesDiscarded |
  	buf := String new: 10000.
  	totalBytesDiscarded := 0.
+ 	[self isConnected and: [self dataAvailable]] whileTrue: [
- 	[self isConnected] whileTrue: [
  		totalBytesDiscarded :=
  			totalBytesDiscarded + (self receiveDataInto: buf)].
  	^ totalBytesDiscarded
  !

Item was changed:
  ----- Method: Socket>>getOption: (in category 'other') -----
  getOption: aName 
  	"Get options on this socket, see Unix man pages for values for 
+ 	sockets, IP, TCP, UDP. IE SO_KEEPALIVE
- 	sockets, IP, TCP, UDP. IE SO:=KEEPALIVE
  	returns an array, element one is an status number (0 ok, -1 read only option)
  	element two is the resulting of the requested option"
  
  	(socketHandle == nil or: [self isValid not])
  		ifTrue: [InvalidSocketStatusException signal: 'Socket status must valid before getting an option'].
  	^self primSocket: socketHandle getOption: aName
  
  "| foo options |
  Socket initializeNetwork.
+ foo _ Socket newTCP.
- foo := Socket newTCP.
  foo connectTo: (NetNameResolver addressFromString: '192.168.1.1') port: 80.
  foo waitForConnectionUntil: (Socket standardDeadline).
  
+ options _ {
+ 'SO_DEBUG'. 'SO_REUSEADDR'. 'SO_REUSEPORT'. 'SO_DONTROUTE'.
+ 'SO_BROADCAST'. 'SO_SNDBUF'. 'SO_RCVBUF'. 'SO_KEEPALIVE'.
+ 'SO_OOBINLINE'. 'SO_PRIORITY'. 'SO_LINGER'. 'SO_RCVLOWAT'.
+ 'SO_SNDLOWAT'. 'IP_TTL'. 'IP_HDRINCL'. 'IP_RCVOPTS'.
+ 'IP_RCVDSTADDR'. 'IP_MULTICAST_IF'. 'IP_MULTICAST_TTL'.
+ 'IP_MULTICAST_LOOP'. 'UDP_CHECKSUM'. 'TCP_MAXSEG'.
+ 'TCP_NODELAY'. 'TCP_ABORT_THRESHOLD'. 'TCP_CONN_NOTIFY_THRESHOLD'. 
+ 'TCP_CONN_ABORT_THRESHOLD'. 'TCP_NOTIFY_THRESHOLD'.
+ 'TCP_URGENT_PTR_TYPE'}.
- options := {
- 'SO:=DEBUG'. 'SO:=REUSEADDR'. 'SO:=REUSEPORT'. 'SO:=DONTROUTE'.
- 'SO:=BROADCAST'. 'SO:=SNDBUF'. 'SO:=RCVBUF'. 'SO:=KEEPALIVE'.
- 'SO:=OOBINLINE'. 'SO:=PRIORITY'. 'SO:=LINGER'. 'SO:=RCVLOWAT'.
- 'SO:=SNDLOWAT'. 'IP:=TTL'. 'IP:=HDRINCL'. 'IP:=RCVOPTS'.
- 'IP:=RCVDSTADDR'. 'IP:=MULTICAST:=IF'. 'IP:=MULTICAST:=TTL'.
- 'IP:=MULTICAST:=LOOP'. 'UDP:=CHECKSUM'. 'TCP:=MAXSEG'.
- 'TCP:=NODELAY'. 'TCP:=ABORT:=THRESHOLD'. 'TCP:=CONN:=NOTIFY:=THRESHOLD'. 
- 'TCP:=CONN:=ABORT:=THRESHOLD'. 'TCP:=NOTIFY:=THRESHOLD'.
- 'TCP:=URGENT:=PTR:=TYPE'}.
  
  1 to: options size do: [:i | | fum |
+ 	fum _foo getOption: (options at: i).
- 	fum :=foo getOption: (options at: i).
  	Transcript show: (options at: i),fum printString;cr].
  
+ foo _ Socket newUDP.
- foo := Socket newUDP.
  foo setPeer: (NetNameResolver addressFromString: '192.168.1.9') port: 7.
  foo waitForConnectionUntil: (Socket standardDeadline).
  
  1 to: options size do: [:i | | fum |
+ 	fum _foo getOption: (options at: i).
- 	fum :=foo getOption: (options at: i).
  	Transcript show: (options at: i),fum printString;cr].
  "!

Item was added:
+ ----- Method: Socket>>initialize:family: (in category 'initialize-destroy') -----
+ initialize: socketType family: family
+ 	"Initialize a new socket handle. If socket creation fails, socketHandle will be set to nil."
+ 	| semaIndex readSemaIndex writeSemaIndex |
+ 
+ 	NetNameResolver useOldNetwork ifTrue: [^self initialize: socketType].
+ 	primitiveOnlySupportsOneSemaphore := false.
+ 	semaphore := Semaphore new.
+ 	readSemaphore := Semaphore new.
+ 	writeSemaphore := Semaphore new.
+ 	semaIndex := Smalltalk registerExternalObject: semaphore.
+ 	readSemaIndex := Smalltalk registerExternalObject: readSemaphore.
+ 	writeSemaIndex := Smalltalk registerExternalObject: writeSemaphore.
+ 	socketHandle :=
+ 		self primSocketCreateNetwork: family
+ 			type: socketType
+ 			receiveBufferSize: 8000
+ 			sendBufSize: 8000
+ 			semaIndex: semaIndex
+ 			readSemaIndex: readSemaIndex
+ 			writeSemaIndex: writeSemaIndex.
+ 
+ 	socketHandle
+ 		ifNotNil: [ self register ]
+ 		ifNil: [  "socket creation failed"
+ 			Smalltalk unregisterExternalObject: semaphore.
+ 			Smalltalk unregisterExternalObject: readSemaphore.
+ 			Smalltalk unregisterExternalObject: writeSemaphore.
+ 			readSemaphore := writeSemaphore := semaphore := nil ]
+ !

Item was added:
+ ----- Method: Socket>>listenWithBacklog: (in category 'ipv6') -----
+ listenWithBacklog: backlogSize
+ 
+ 	| status |
+ 	self initializeNetwork.
+ 	status := self primSocketConnectionStatus: socketHandle.
+ 	(status == Unconnected)
+ 		ifFalse: [InvalidSocketStatusException signal: 'Socket status must Unconnected before it can listen for connections'].
+ 
+ 	self primSocket: socketHandle listenWithBacklog: backlogSize.
+ !

Item was added:
+ ----- Method: Socket>>localSocketAddress (in category 'ipv6') -----
+ localSocketAddress
+ 
+ 	| size addr |
+ 	size := self primSocketLocalAddressSize: socketHandle.
+ 	addr := SocketAddress new: size.
+ 	self primSocket: socketHandle localAddressResult: addr.
+ 	^addr!

Item was changed:
  ----- Method: Socket>>peerName (in category 'accessing') -----
  peerName
  	"Return the name of the host I'm connected to, or nil if its name isn't known to the domain name server or the request times out."
  	"Note: Slow. Calls the domain name server, taking up to 20 seconds to time out. Even when sucessful, delays of up to 13 seconds have been observed during periods of high network load." 
  
+ 	^self remoteSocketAddress hostName!
- 	^ NetNameResolver
- 		nameForAddress: self remoteAddress
- 		timeout: 20
- !

Item was added:
+ ----- Method: Socket>>primSocket:bindTo: (in category 'primitives-ipv6') -----
+ primSocket: socketID bindTo: socketAddress
+ 
+ 	<primitive: 'primitiveSocketBindTo' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was added:
+ ----- Method: Socket>>primSocket:connectTo: (in category 'primitives-ipv6') -----
+ primSocket: socketID connectTo: socketAddress
+ 
+ 	<primitive: 'primitiveSocketConnectTo' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was changed:
  ----- Method: Socket>>primSocket:getOption: (in category 'primitives') -----
  primSocket: socketID getOption: aString 
  	"Get some option information on this socket. Refer to the UNIX 
  	man pages for valid SO, TCP, IP, UDP options. In case of doubt
  	refer to the source code.
+ 	TCP_NODELAY, SO_KEEPALIVE are valid options for example
- 	TCP:=NODELAY, SO:=KEEPALIVE are valid options for example
  	returns an array containing the error code and the option value"
  
  	<primitive: 'primitiveSocketGetOptions' module: 'SocketPlugin'>
  	self primitiveFailed
  !

Item was added:
+ ----- Method: Socket>>primSocket:listenWithBacklog: (in category 'primitives-ipv6') -----
+ primSocket: socketID listenWithBacklog: backlogSize
+ 
+ 	<primitive: 'primitiveSocketListenWithBacklog' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was added:
+ ----- Method: Socket>>primSocket:localAddressResult: (in category 'primitives-ipv6') -----
+ primSocket: socketID localAddressResult: socketAddress
+ 
+ 	<primitive: 'primitiveSocketLocalAddressResult' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was added:
+ ----- Method: Socket>>primSocket:remoteAddressResult: (in category 'primitives-ipv6') -----
+ primSocket: socketID remoteAddressResult: socketAddress
+ 
+ 	<primitive: 'primitiveSocketRemoteAddressResult' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was changed:
  ----- Method: Socket>>primSocket:setOption:value: (in category 'primitives') -----
  primSocket: socketID setOption: aString value: aStringValue
  	"Set some option information on this socket. Refer to the UNIX 
  	man pages for valid SO, TCP, IP, UDP options. In case of doubt
  	refer to the source code.
+ 	TCP_NODELAY, SO_KEEPALIVE are valid options for example
- 	TCP:=NODELAY, SO:=KEEPALIVE are valid options for example
  	returns an array containing the error code and the negotiated value"
  
  	<primitive: 'primitiveSocketSetOptions' module: 'SocketPlugin'>
  	^nil!

Item was added:
+ ----- Method: Socket>>primSocketLocalAddressSize: (in category 'primitives-ipv6') -----
+ primSocketLocalAddressSize: handle
+ 
+ 	<primitive: 'primitiveSocketLocalAddressSize' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was changed:
  ----- Method: Socket>>primSocketReceiveDataAvailable: (in category 'primitives') -----
  primSocketReceiveDataAvailable: socketID
  	"Return true if data may be available for reading from the current socket."
  
  	<primitive: 'primitiveSocketReceiveDataAvailable' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !
- 	SocketPrimitiveFailed signal!

Item was added:
+ ----- Method: Socket>>primSocketRemoteAddressSize: (in category 'primitives-ipv6') -----
+ primSocketRemoteAddressSize: handle
+ 
+ 	<primitive: 'primitiveSocketRemoteAddressSize' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was added:
+ ----- Method: Socket>>remoteSocketAddress (in category 'ipv6') -----
+ remoteSocketAddress
+ 
+ 	NetNameResolver useOldNetwork
+ 		ifTrue: [^(self primSocketRemoteAddress: socketHandle) asSocketAddress]
+ 		ifFalse: [
+ 			| size addr |
+ 			size := self primSocketRemoteAddressSize: socketHandle.
+ 			addr := SocketAddress new: size.
+ 			self primSocket: socketHandle remoteAddressResult: addr.
+ 			^addr]!

Item was changed:
  ----- Method: Socket>>sendStreamContents:checkBlock: (in category 'sending') -----
  sendStreamContents: stream checkBlock: checkBlock
  	"Send the data in the stream. Close the stream after you are done. After each block of data evaluate checkBlock and abort if it returns false.
  	Usefull for directly sending contents of a file without reading into memory first."
+ 
- 	[
  	| chunkSize buffer |
  	chunkSize := 5000.
  	buffer := ByteArray new: chunkSize.
  	stream binary.
+ 	[[stream atEnd and: [checkBlock value]]
- 	[stream atEnd and: [checkBlock value]]
  		whileFalse: [
  			buffer := stream next: chunkSize into: buffer.
  			self sendData: buffer]]
  		ensure: [stream close]!

Item was changed:
  ----- Method: Socket>>setOption:value: (in category 'other') -----
  setOption: aName value: aValue 
  	| value |
  	"setup options on this socket, see Unix man pages for values for 
+ 	sockets, IP, TCP, UDP. IE SO_KEEPALIVE
- 	sockets, IP, TCP, UDP. IE SO:=KEEPALIVE
  	returns an array, element one is the error number
  	element two is the resulting of the negotiated value.
  	See getOption for list of keys"
  
  	(socketHandle == nil or: [self isValid not])
  		ifTrue: [InvalidSocketStatusException signal: 'Socket status must valid before setting an option'].
  	value := aValue asString.
  	aValue == true ifTrue: [value := '1'].
  	aValue == false ifTrue: [value := '0'].
  	^ self primSocket: socketHandle setOption: aName value: value!

Item was added:
+ ----- Method: Socket>>waitForConnectionUntil: (in category 'waiting') -----
+ 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
+ !

Item was added:
+ ByteArray variableByteSubclass: #SocketAddress
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Network-Kernel'!
+ 
+ !SocketAddress commentStamp: '<historical>' prior: 0!
+ I represent a socket (network) address consisting of a host internet address and a port number.  My contents are opaque and cannot be interpreted directly.  See the accessing protocol for methods that retrieve the information I contain.!

Item was added:
+ ----- Method: SocketAddress classSide>>fromOldByteAddress: (in category 'instance creation') -----
+ fromOldByteAddress: byteArray
+ 	^self newFrom: byteArray!

Item was added:
+ ----- Method: SocketAddress classSide>>loopback4 (in category 'accessing') -----
+ loopback4
+ 
+ 	^self loopbacks4 first!

Item was added:
+ ----- Method: SocketAddress classSide>>loopback6 (in category 'accessing') -----
+ loopback6
+ 
+ 	^self loopbacks6 first!

Item was added:
+ ----- Method: SocketAddress classSide>>loopbacks (in category 'accessing') -----
+ loopbacks
+ 
+ 	^SocketAddressInformation forHost: '' service: '0'
+ 		flags:			0
+ 		addressFamily:	0
+ 		socketType:		0
+ 		protocol:		0!

Item was added:
+ ----- Method: SocketAddress classSide>>loopbacks4 (in category 'accessing') -----
+ loopbacks4
+ 
+ 	^SocketAddressInformation forHost: 'localhost' service: ''
+ 		flags:			0
+ 		addressFamily:	SocketAddressInformation addressFamilyINET4
+ 		socketType:		0
+ 		protocol:		0!

Item was added:
+ ----- Method: SocketAddress classSide>>loopbacks6 (in category 'accessing') -----
+ loopbacks6
+ 
+ 	^SocketAddressInformation forHost: '' service: '0'
+ 		flags:			0
+ 		addressFamily:	SocketAddressInformation addressFamilyINET6
+ 		socketType:		0
+ 		protocol:		0!

Item was added:
+ ----- Method: SocketAddress classSide>>wildcard4 (in category 'accessing') -----
+ wildcard4
+ 
+ 	^self wildcards4 first!

Item was added:
+ ----- Method: SocketAddress classSide>>wildcard6 (in category 'accessing') -----
+ wildcard6
+ 
+ 	^self wildcards6 first!

Item was added:
+ ----- Method: SocketAddress classSide>>wildcards (in category 'accessing') -----
+ wildcards
+ 
+ 	^SocketAddressInformation forHost: '' service: '0'
+ 		flags:			SocketAddressInformation passiveFlag
+ 		addressFamily:	0
+ 		socketType:		0
+ 		protocol:		0!

Item was added:
+ ----- Method: SocketAddress classSide>>wildcards4 (in category 'accessing') -----
+ wildcards4
+ 
+ 	^SocketAddressInformation forHost: '' service: '0'
+ 		flags:			SocketAddressInformation passiveFlag
+ 		addressFamily:	SocketAddressInformation addressFamilyINET4
+ 		socketType:		SocketAddressInformation socketTypeStream
+ 		protocol:		0!

Item was added:
+ ----- Method: SocketAddress classSide>>wildcards6 (in category 'accessing') -----
+ wildcards6
+ 
+ 	^SocketAddressInformation forHost: '' service: '0'
+ 		flags:			SocketAddressInformation passiveFlag
+ 		addressFamily:	SocketAddressInformation addressFamilyINET6
+ 		socketType:		0
+ 		protocol:		0!

Item was added:
+ ----- Method: SocketAddress>>asSocketAddress (in category 'converting') -----
+ asSocketAddress
+ !

Item was added:
+ ----- Method: SocketAddress>>hostName (in category 'accessing') -----
+ hostName
+ 
+ 	| size name |
+ 	NetNameResolver primGetNameInfo: self flags: 0.
+ 	size := NetNameResolver primGetNameInfoHostSize.
+ 	name := String new: size.
+ 	NetNameResolver primGetNameInfoHostResult: name.
+ 	^name!

Item was added:
+ ----- Method: SocketAddress>>hostNumber (in category 'accessing') -----
+ hostNumber
+ 
+ 	| size name |
+ 	NetNameResolver primGetNameInfo: self flags: 1.
+ 	size := NetNameResolver primGetNameInfoHostSize.
+ 	name := String new: size.
+ 	NetNameResolver primGetNameInfoHostResult: name.
+ 	^name!

Item was added:
+ ----- Method: SocketAddress>>port (in category 'primitives') -----
+ port
+ 
+ 	<primitive: 'primitiveSocketAddressGetPort' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was added:
+ ----- Method: SocketAddress>>port: (in category 'primitives') -----
+ port: anInteger
+ 
+ 	<primitive: 'primitiveSocketAddressSetPort' module: 'SocketPlugin'>
+ 	self primitiveFailed
+ !

Item was added:
+ ----- Method: SocketAddress>>printOn: (in category 'printing') -----
+ printOn: aStream
+ 
+ 	aStream
+ 		nextPutAll: self hostNumber;
+ 		nextPut: $(; nextPutAll: self hostName; nextPut: $);
+ 		nextPut: $,;
+ 		nextPutAll: self serviceNumber;
+ 		nextPut: $(; nextPutAll: self serviceName; nextPut: $)!

Item was added:
+ ----- Method: SocketAddress>>serviceName (in category 'accessing') -----
+ serviceName
+ 
+ 	| size name |
+ 	NetNameResolver primGetNameInfo: self flags: 0.
+ 	size := NetNameResolver primGetNameInfoServiceSize.
+ 	name := String new: size.
+ 	NetNameResolver primGetNameInfoServiceResult: name.
+ 	^name!

Item was added:
+ ----- Method: SocketAddress>>serviceNumber (in category 'accessing') -----
+ serviceNumber
+ 
+ 	| size name |
+ 	NetNameResolver primGetNameInfo: self flags: 1.
+ 	size := NetNameResolver primGetNameInfoServiceSize.
+ 	name := String new: size.
+ 	NetNameResolver primGetNameInfoServiceResult: name.
+ 	^name!

Item was added:
+ Object subclass: #SocketAddressInformation
+ 	instanceVariableNames: 'socketAddress addressFamily socketType protocol'
+ 	classVariableNames: 'AddressFamilyINET4 AddressFamilyINET6 AddressFamilyLocal AddressFamilyUnspecified NumericFlag PassiveFlag ProtocolTCP ProtocolUDP ProtocolUnspecified SocketTypeDGram SocketTypeStream SocketTypeUnspecified'
+ 	poolDictionaries: ''
+ 	category: 'Network-Kernel'!
+ 
+ !SocketAddressInformation commentStamp: '<historical>' prior: 0!
+ I represent a local or remote network service.
+ 
+ Instance Variables
+ 	addressFamily:	<SmallInteger> the address family (unix, inet4, inet6, ...) in which the service address is available.
+ 	protocol:		<SmallInteger> the protocol (tcp, udp, ...) that the service uses.
+ 	socketAddress:	<SocketAddress> the socket address at which the service can be contacted or created.
+ 	socketType:		<SmallInteger> the type (stream, dgram) of the socket that should be created for communication with the service.
+ !

Item was added:
+ ----- Method: SocketAddressInformation classSide>>addressFamilyINET4 (in category 'accessing') -----
+ addressFamilyINET4
+ 
+ 	^AddressFamilyINET4!

Item was added:
+ ----- Method: SocketAddressInformation classSide>>addressFamilyINET6 (in category 'accessing') -----
+ addressFamilyINET6
+ 
+ 	^AddressFamilyINET6!

Item was added:
+ ----- Method: SocketAddressInformation classSide>>addressFamilyLocal (in category 'accessing') -----
+ addressFamilyLocal
+ 
+ 	^AddressFamilyLocal!

Item was added:
+ ----- Method: SocketAddressInformation classSide>>addressFamilyUnspecified (in category 'accessing') -----
+ addressFamilyUnspecified
+ 
+ 	^AddressFamilyUnspecified!

Item was added:
+ ----- Method: SocketAddressInformation classSide>>forHost:service:flags:addressFamily:socketType:protocol: (in category 'instance creation') -----
+ forHost: hostName service: servName flags: flags addressFamily: family socketType: type protocol: protocol
+ 
+ 	| result addr |
+ 	NetNameResolver initializeNetwork.
+ 	NetNameResolver primGetAddressInfoHost: hostName service: servName flags: flags family: family type: type protocol: protocol.
+ 	result := OrderedCollection new.
+ 	[(addr := NetNameResolver nextSocketAddressInformation) notNil] whileTrue: [result add: addr].
+ 	^result!

Item was added:
+ ----- Method: SocketAddressInformation classSide>>initialize (in category 'class initialization') -----
+ initialize			"SocketAddressInformation initialize"
+ 
+ 	NumericFlag := 1.
+ 	PassiveFlag := 2.
+ 	AddressFamilyUnspecified := 0.
+ 	AddressFamilyLocal := 1.
+ 	AddressFamilyINET4 := 2.
+ 	AddressFamilyINET6 := 3.
+ 	SocketTypeUnspecified := 0.
+ 	SocketTypeStream := 1.
+ 	SocketTypeDGram := 2.
+ 	ProtocolUnspecified := 0.
+ 	ProtocolTCP := 1.
+ 	ProtocolUDP := 2.!

Item was added:
+ ----- Method: SocketAddressInformation classSide>>numericFlag (in category 'accessing') -----
+ numericFlag
+ 
+ 	^NumericFlag!

Item was added:
+ ----- Method: SocketAddressInformation classSide>>passiveFlag (in category 'accessing') -----
+ passiveFlag
+ 
+ 	^PassiveFlag!

Item was added:
+ ----- Method: SocketAddressInformation classSide>>protocolTCP (in category 'accessing') -----
+ protocolTCP
+ 
+ 	^ProtocolTCP!

Item was added:
+ ----- Method: SocketAddressInformation classSide>>protocolUDP (in category 'accessing') -----
+ protocolUDP
+ 
+ 	^ProtocolUDP!

Item was added:
+ ----- Method: SocketAddressInformation classSide>>protocolUnspecified (in category 'accessing') -----
+ protocolUnspecified
+ 
+ 	^ProtocolUnspecified!

Item was added:
+ ----- Method: SocketAddressInformation classSide>>socketTypeDGram (in category 'accessing') -----
+ socketTypeDGram
+ 
+ 	^SocketTypeDGram!

Item was added:
+ ----- Method: SocketAddressInformation classSide>>socketTypeStream (in category 'accessing') -----
+ socketTypeStream
+ 
+ 	^SocketTypeStream!

Item was added:
+ ----- Method: SocketAddressInformation classSide>>socketTypeUnspecified (in category 'accessing') -----
+ socketTypeUnspecified
+ 
+ 	^SocketTypeUnspecified!

Item was added:
+ ----- Method: SocketAddressInformation classSide>>withSocketAddress:family:type:protocol: (in category 'instance creation') -----
+ withSocketAddress: socketAddress family: family type: type protocol: protocol
+ 
+ 	^self new initSocketAddress: socketAddress family: family type: type protocol: protocol!

Item was added:
+ ----- Method: SocketAddressInformation>>addressFamilyName (in category 'accessing') -----
+ addressFamilyName
+ 
+ 	^#(unspecified local inet4 inet6) at: addressFamily + 1!

Item was added:
+ ----- Method: SocketAddressInformation>>connect (in category 'circuit setup') -----
+ connect
+ 
+ 	| sock |
+ 	socketType == SocketTypeStream ifFalse: [^nil].
+ 	sock := Socket newTCP: addressFamily.
+ 	sock connectTo: socketAddress.
+ 	sock waitForConnectionFor: Socket standardTimeout
+ 		ifTimedOut: [ConnectionTimedOut signal: 'Cannot connect to ', self printString].
+ 	^sock!

Item was added:
+ ----- Method: SocketAddressInformation>>initSocketAddress:family:type:protocol: (in category 'initialize-release') -----
+ initSocketAddress: aSocketAddress family: familyInteger type: typeInteger protocol: protocolInteger
+ 
+ 	socketAddress := aSocketAddress.
+ 	addressFamily := familyInteger.
+ 	socketType := typeInteger.
+ 	protocol := protocolInteger.!

Item was added:
+ ----- Method: SocketAddressInformation>>listenWithBacklog: (in category 'circuit setup') -----
+ listenWithBacklog: backlog
+ 
+ 	| sock |
+ 	(socketType == SocketTypeStream and: [protocol == ProtocolTCP]) ifFalse: [self error: 'cannot listen'].
+ 	sock := Socket newTCP: addressFamily.
+ 	sock bindTo: socketAddress.
+ 	sock listenWithBacklog: 5.
+ 	^sock!

Item was added:
+ ----- Method: SocketAddressInformation>>printOn: (in category 'printing') -----
+ printOn: aStream
+ 
+ 	aStream
+ 		print: socketAddress;
+ 		nextPut: $-; nextPutAll: self addressFamilyName;
+ 		nextPut: $-; nextPutAll: self socketTypeName;
+ 		nextPut: $-; nextPutAll: self protocolName!

Item was added:
+ ----- Method: SocketAddressInformation>>protocolName (in category 'accessing') -----
+ protocolName
+ 
+ 	^#(unspecified tcp udp) at: socketType + 1!

Item was added:
+ ----- Method: SocketAddressInformation>>socketAddress (in category 'accessing') -----
+ socketAddress
+ 
+ 	^socketAddress!

Item was added:
+ ----- Method: SocketAddressInformation>>socketTypeName (in category 'accessing') -----
+ socketTypeName
+ 
+ 	^#(unspecified stream dgram) at: socketType + 1!




More information about the Squeak-dev mailing list