@@ -450,7 +450,18 @@ Socket >> address [
450450
451451{ #category : #' initialize - destroy' }
452452Socket >> bindTo: anAddress port: aPort [
453- ^ self primSocket: socketHandle bindTo: anAddress port: aPort
453+ " Bind to the local port <aPort>, on the interface specified by <anAddress>
454+ (`SocketAddress zero` specifies all interfaces).
455+ Primarily used to prepare to listen for incoming connections with #listen[WithBacklog:]."
456+
457+ self primSocket: socketHandle bindTo: anAddress port: aPort
458+ ]
459+
460+ { #category : #' initialize - destroy' }
461+ Socket >> bindToPort: aPort [
462+ " Bind to the local port <aPort>, often in order to listen for incoming connections."
463+
464+ self bindTo: SocketAddress zero port: aPort
454465]
455466
456467{ #category : #' private - errors' }
@@ -738,37 +749,52 @@ Socket >> isWaitingForConnection [
738749]
739750
740751{ #category : #' connection open/close' }
741- Socket >> listenOn: port [
742- " Listen for a connection on the given port. This operation will return immediately; follow it with waitForConnectionUntil: to wait until a connection is established."
752+ Socket >> listen [
753+ " Listen for a connection (after binding to a port using #bindTo:port:).
754+ If this method succeeds, you must wait for a connection attempt with #waitForConnectionFor:,
755+ then #accept may be used to establish a new connection"
743756
744- | status |
745- status := self primSocketConnectionStatus: socketHandle.
746- (status == Unconnected )
747- ifFalse: [InvalidSocketStatusException signal : ' Socket status must Unconnected before listening for a new connection' ].
757+ self listenWithBacklog: 1
758+ ]
748759
749- self primSocket: socketHandle listenOn: port
760+ { #category : #' connection open/close' }
761+ Socket >> listenOn: port [
762+
763+ self
764+ bindToPort: port;
765+ listen
750766]
751767
752768{ #category : #' connection open/close' }
753769Socket >> listenOn: portNumber backlogSize: backlog [
754- " Listen for a connection on the given port.
755- If this method succeeds, #accept may be used to establish a new connection"
756- | status |
757- status := self primSocketConnectionStatus: socketHandle.
758- (status == Unconnected )
759- ifFalse: [InvalidSocketStatusException signal : ' Socket status must Unconnected before listening for a new connection' ].
760- self primSocket: socketHandle listenOn: portNumber backlogSize: backlog
770+
771+ self
772+ bindToPort: portNumber;
773+ listenWithBacklog: backlog
761774]
762775
763776{ #category : #' connection open/close' }
764777Socket >> listenOn: portNumber backlogSize: backlog interface: ifAddr [
765- " Listen for a connection on the given port.
766- If this method succeeds, #accept may be used to establish a new connection"
778+
779+ self
780+ bindTo: ifAddr port: portNumber;
781+ listenWithBacklog: backlog
782+ ]
783+
784+ { #category : #' connection open/close' }
785+ Socket >> listenWithBacklog: anIntegerBacklog [
786+ " Listen for a connection, allowing <anIntegerBacklog> connections to be queued by the OS.
787+ Must already be bound to a port using #bindTo:port:.
788+ If this method succeeds, you must wait for a connection attempt with #waitForConnectionFor:,
789+ then #accept may be used to establish a new connection"
790+
767791 | status |
768792 status := self primSocketConnectionStatus: socketHandle.
769- (status == Unconnected )
770- ifFalse: [InvalidSocketStatusException signal : ' Socket status must Unconnected before listening for a new connection' ].
771- self primSocket: socketHandle listenOn: portNumber backlogSize: backlog interface: ifAddr
793+ status == Unconnected ifFalse: [
794+ InvalidSocketStatusException signal :
795+ ' Socket status must Unconnected before listening for a new connection' ].
796+
797+ self primSocket: socketHandle listenWithBacklog: anIntegerBacklog
772798]
773799
774800{ #category : #accessing }
@@ -873,30 +899,6 @@ Socket >> primSocket: socketID getOption: aString [
873899 ^ SocketError signal : self socketErrorMessage
874900]
875901
876- { #category : #primitives }
877- Socket >> primSocket: socketID listenOn: port [
878- " Listen for a connection on the given port. This is an asynchronous call; query the socket status to discover if and when the connection is actually completed."
879-
880- < primitive: ' primitiveSocketListenWithOrWithoutBacklog' module: ' SocketPlugin' >
881- ^ SocketError signal : self socketErrorMessage
882- ]
883-
884- { #category : #primitives }
885- Socket >> primSocket: aHandle listenOn: portNumber backlogSize: backlog [
886- " Primitive. Set up the socket to listen on the given port.
887- Will be used in conjunction with #accept only."
888- < primitive: ' primitiveSocketListenWithOrWithoutBacklog' module: ' SocketPlugin' >
889- self destroy. " Accept not supported so clean up"
890- ]
891-
892- { #category : #primitives }
893- Socket >> primSocket: aHandle listenOn: portNumber backlogSize: backlog interface: ifAddr [
894- " Primitive. Set up the socket to listen on the given port.
895- Will be used in conjunction with #accept only."
896- < primitive: ' primitiveSocketListenOnPortBacklogInterface' module: ' SocketPlugin' >
897- self destroy. " Accept not supported so clean up"
898- ]
899-
900902{ #category : #' primitives - ipv6' }
901903Socket >> primSocket: socketID listenWithBacklog: backlogSize [
902904
0 commit comments