Socket.st
author Stefan Vogel <sv@exept.de>
Wed, 22 Sep 1999 11:44:57 +0200
changeset 820 b6860c3660c8
parent 819 4cc15700d123
child 821 40b0b69bf4b5
permissions -rw-r--r--
Fix address sizes when calling gethostbyaddr (accept returns size including port, gethostbyaddr wants size of ip address only)

"
 COPYRIGHT (c) 1992 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

NonPositionableExternalStream subclass:#Socket
	instanceVariableNames:'domain socketType protocol port serviceName peerName'
	classVariableNames:''
	poolDictionaries:''
	category:'Streams-External'
!

!Socket primitiveDefinitions!
%{

#ifdef LINUX
# define BUGGY_STDIO_LIB
#endif

#include <stdio.h>
#include <errno.h>

#define UNIX_LIKE

#if defined(transputer)
# undef UNIX_LIKE
# define NO_SOCKET
#endif

/*
 * which protocols can we support ?
 */
#ifndef NO_SOCKET
# define WANT__AF_INET
#endif

#ifdef UNIX_LIKE
# define WANT__AF_UNIX
#endif

#ifdef __VMS__
# undef WANT__AF_UNIX
# define WANT_AF_DECnet
#endif

#ifdef LINUX
# define WANT__AF_APPLETALK
# define xxWANT__AF_X25
# define xxWANT__AF_AX25
# define xxWANT__AF_IPX
# define WANT__AF_INET6 */
#endif

#ifdef solaris2_0
# define xxxWANT__AF_DECNET
#endif

#ifdef LINUX
/* kludge to avoid some redefines ... */
# define _ARPA_NAMESER_H
# define _NETINET_TCP_H
#endif

#if !defined(NO_SOCKET)
# include <fcntl.h>
# include <sys/types.h>
# define _SYS_TYPES_H_INCLUDED_

# if defined(IRIS) && !defined(IRIX5)
   /* no socket.h on 4.0.5h ?!?!? */
#  ifndef AF_UNIX
#   define AF_UNIX 1
#  endif
#  ifndef AF_INET
#   define AF_INET 2
#  endif

#  ifndef SOCK_STREAM
#   define SOCK_STREAM 1
#  endif
#  ifndef SOCK_DGRAM
#   define SOCK_DGRAM  2
#  endif
#  ifndef SOCK_RAW
#   define SOCK_RAW    3
#  endif
# else
#  include <sys/socket.h>
# endif

# ifdef NEXT3
#  include <netinet/in_systm.h>
# endif
#endif


/*
 * see what we want ...
 */
#ifdef WANT__AF_UNIX
# ifdef AF_UNIX
#  ifndef PF_UNIX
#   define PF_UNIX AF_UNIX
#  endif
# endif
#else
# undef AF_UNIX
#endif

#ifdef WANT__AF_INET
# ifdef AF_INET
#  ifndef PF_INET
#   define PF_INET AF_INET
#  endif
# endif
#else
# undef AF_INET
#endif

#ifdef WANT__AF_INET6
# ifdef AF_INET6
#  ifndef PF_INET6
#   define PF_INET6 AF_INET6
#  endif
# endif
#else
# undef AF_INET6
#endif

#ifdef WANT__AF_DECnet
# ifdef AF_DECnet
#  ifndef PF_DECnet
#   define PF_DECnet AF_DECnet
#  endif
# endif
#else
# undef AF_DECnet
#endif

#ifdef WANT__AF_APPLETALK
# ifdef AF_APPLETALK
#  ifndef PF_APPLETALK
#   define PF_APPLETALK AF_APPLETALK
#  endif
# endif
#else
# undef AF_APPLETALK
#endif

#ifdef WANT__AF_X25     /* X.25 */
# ifdef AF_X25
#  ifndef PF_X25
#   define PF_X25 AF_X25
#  endif
# endif
#else
# undef AF_X25
#endif

#ifdef WANT__AF_NS      /* Xerox XNS */
# ifdef AF_NS
#  ifndef PF_NS
#   define PF_NS AF_NS
#  endif
# endif
#else
# undef AF_NS
#endif

#ifdef WANT__AF_SNA     /* IBM SNA */
# ifdef AF_SNA
#  ifndef PF_SNA
#   define PF_SNA AF_SNA
#  endif
# endif
#else
# undef AF_SNA
#endif

#ifdef WANT__AF_RAW     /* RAW packets */
# ifdef AF_RAW
#  ifndef PF_RAW
#   define PF_RAW AF_RAW
#  endif
# endif
#else
# undef AF_RAW
#endif

#ifdef WANT__AF_ISO     /* ? */
# ifdef AF_ISO
#  ifndef PF_ISO
#   define PF_ISO AF_ISO
#  endif
# endif
#else
# undef AF_ISO
#endif

#ifdef WANT__AF_NETBIOS /* ? */
# ifdef AF_NETBIOS
#  ifndef PF_NETBIOS
#   define PF_NETBIOS AF_NETBIOS
#  endif
# endif
#else
# undef AF_NETBIOS
#endif

#ifdef WANT__AF_CCITT /* ? */
# if defined(AF_CCITT) && (AF_CCITT != AF_X25)
#  ifndef PF_CCITT
#   define PF_CCITT AF_CCITT
#  endif
# endif
#else
# undef AF_CCITT
#endif

#ifdef WANT__AF_IPX /* Novell IPX */
# ifdef AF_IPX
#  ifndef PF_IPX
#   define PF_IPX AF_IPX
#  endif
# endif
#else
# undef AF_IPX
#endif

#ifdef WANT__AF_AX25 /* Amateur Radio AX.25 */
# ifdef AF_AX25
#  ifndef PF_AX25
#   define PF_AX25 AF_AX25
#  endif
# endif
#else
# undef AF_AX25
#endif

#ifdef WANT__AF_NETROM /* Amateur Radio NET/ROM */
# ifdef AF_NETROM
#  ifndef PF_NETROM
#   define PF_NETROM AF_NETROM
#  endif
# endif
#else
# undef AF_NETROM
#endif

#ifdef WANT__AF_BRIDGE /* multiprotocol bridge */
# ifdef AF_BRIDGE
#  ifndef PF_BRIDGE
#   define PF_BRIDGE AF_BRIDGE
#  endif
# endif
#else
# undef AF_BRIDGE
#endif

#ifdef WANT__AF_BSC /* BISYNC 2780/3780 */
# ifdef AF_BSC
#  ifndef PF_BSC
#   define PF_BSC AF_BSC
#  endif
# endif
#else
# undef AF_BSC
#endif

#ifdef WANT__AF_ROSE /* Amateur Radio X.25 PLP */
# ifdef AF_ROSE
#  ifndef PF_ROSE
#   define PF_ROSE AF_ROSE
#  endif
# endif
#else
# undef AF_ROSE
#endif


/*
 * now, include what we have to ...
 * undef support, if no include file is present
 * (or I dont know yet, where to find it)
 */

#ifdef AF_INET
# include <netdb.h>
# if defined(LINUX) && defined(AF_INET6)
#  include <linux/in.h>
# else
#  include <netinet/in.h>
# endif
# if ! (defined(SYSV3) && defined(mc88k))
#  include <netinet/tcp.h>
# endif
#endif

#ifdef AF_INET6
# if defined(LINUX) && defined(__GLIBC__)
#  include <linux/in6.h>
# else
#  undef AF_INET6
# endif
#endif

#ifdef AF_UNIX
# include <sys/un.h>
#endif

#ifdef AF_APPLETALK
# ifdef LINUX
#  include <asm/types.h>
#  include <linux/atalk.h>
# else
#  undef AF_APPLETALK
# endif
#endif

#ifdef AF_DECNET
# ifdef solaris2_0
#  include <X11/dni8.h>
# else
#  undef AF_DECNET
# endif
#endif

#ifdef AF_X25
# ifdef LINUX
#  include <linux/x25.h>
# else
#  undef AF_X25
# endif
#endif

#ifdef AF_AX25
# ifdef LINUX
#  include <linux/ax25.h>
# else
#  undef AF_AX25
# endif
#endif

#ifdef AF_IPX
# ifdef LINUX
#  include <linux/ipx.h>
# else
#  undef AF_IPX
# endif
#endif


/*
 * see what is leftOver
 */
union sockaddr_u {
#ifdef AF_UNIX
	struct sockaddr_un un;
#endif
#ifdef AF_INET
	struct sockaddr_in in;
#endif
#ifdef AF_INET6
	struct sockaddr_in6 in6;
#endif
#ifdef AF_APPLETALK
	struct sockaddr_at at;
#endif
#ifdef AF_DECNET
	struct sockaddr_dn dn;
#endif
#ifdef AF_X25
	struct sockaddr_x25 x25;
#endif
#ifdef AF_AX25
	struct sockaddr_ax25 ax25;
#endif
#ifdef AF_IPX
	struct sockaddr_ipx ipx;
#endif
};


#if defined(TRY_AGAIN) || defined(HOST_NOT_FOUND)
# define USE_H_ERRNO
#endif



/*
 * on some systems errno is a macro ... check for it here
 */
#ifndef errno
 extern errno;
#endif

#ifdef USE_H_ERRNO
# ifndef h_errno
 extern h_errno;
# endif
#endif

#ifdef xxLINUX
/* use inline string macros ... */
# define __STRINGDEFS__
# include <linuxIntern.h>
#endif

/*
 * gethostbyname seems to have trouble
 * sometimes, if interrupted while a request
 * is on its way the name server.
 * (although specified in the man-page, 
 * a check on TRY_AGAIN fails on iris)
 */
#ifdef LINUX

# define GETHOSTBYNAME(hp, name) \
	hp = gethostbyname((char *) name);

# define GETHOSTBYADDR(hp, addr, alen, af) \
	hp = gethostbyaddr(addr, alen, af);

#else

# ifdef IRIX5_3
#  define GETHOSTBYNAME(hp, name) \
	do { \
	    __BEGIN_INTERRUPTABLE__  \
	    hp = gethostbyname((char *) name); \
	    __END_INTERRUPTABLE__ \
	} while ((hp == NULL) && \
		 ((h_errno == TRY_AGAIN) || (errno == ECONNREFUSED)));

#  define GETHOSTBYADDR(hp, addr, alen, af) \
	do { \
	    __BEGIN_INTERRUPTABLE__ \
	    hp = gethostbyaddr(addr, alen, af); \
	    __END_INTERRUPTABLE__ \
	} while ((hp == NULL) && \
		((h_errno == TRY_AGAIN) || (errno == ECONNREFUSED)));
# else
#  ifdef USE_H_ERRNO
#   define GETHOSTBYNAME(hp, name) \
	do { \
	    __BEGIN_INTERRUPTABLE__  \
	    hp = gethostbyname((char *) name); \
	    __END_INTERRUPTABLE__ \
	} while ((hp == NULL) && (h_errno == TRY_AGAIN));

#   define GETHOSTBYADDR(hp, addr, alen, af) \
	do { \
	    __BEGIN_INTERRUPTABLE__  \
	    hp = gethostbyaddr(addr, alen, af); \
	    __END_INTERRUPTABLE__ \
	} while ((hp == NULL) && (h_errno == TRY_AGAIN));
#  else
#   define GETHOSTBYNAME(hp, name) \
	__BEGIN_INTERRUPTABLE__  \
	hp = gethostbyname((char *) name); \
	__END_INTERRUPTABLE__ 

#   define GETHOSTBYADDR(hp, addr, alen, af) \
	__BEGIN_INTERRUPTABLE__ \
	hp = gethostbyaddr(addr, alen, af); \
	__END_INTERRUPTABLE__
#  endif
# endif
#endif

#ifdef DEBUG
# define DBGPRINTF(x)    { if (__debugging__) printf x; }
#else
# define DBGPRINTF(x)    /* as nothing */
#endif

%}
! !

!Socket primitiveVariables!
%{
static int __debugging__ = 0;
%}
! !

!Socket class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1992 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    This class provides access to sockets for interprocess communication.
    The message protocol is preliminary, until someone tells me how
    other smalltalk's socket interfaces look like.

    Currently, only IP and UNIX domain sockets are supported.
    Code for appletalk is included, but was never tested ...
    More may be added in the future.
    (the code is prepared for things like SNA or decNet;
     however, right now, this code is empty and needs a little work.
     Implementing those is pretty straight forward, once the address
     data structures are known.)

    Due to historic reasons (I started this class, before I got hold of some
    code using ST-80 Sockets i.e. RemoteInvocation), there is some old interface
    still provided. 
    This will vanish; use the #family:type: or #newTCPxxx and #newUDPxxx interfaces,
    together with the bind/listen and accept calls,
    which are meant to be compatible to ST-80's UnixSocketAccessor interface.

    ST/X does not use IPSocketAddress, UDSocketAddress etc; all addressing
    is done by passing appropriate string- or byteArray objects containing
    the addresses. This may change, too.

    TODO: cleanup historic leftovers, implement other than inet domain stuff.
	  (mhmh - how can I test those ?)
	  change to raise more signals on errors.
	  Help - could someone who has a linux machine connected to an appletalk
		 net please test this (and send bug fixes ...)

    [author:]
	Claus Gittinger
"
!

examples
"
    example (get help info from an nntp server):
									[exBegin]
	|sock host|

	host := OperatingSystem getEnvironment:'NNTPSERVER'.

	sock := Socket newTCPclientToHost:host port:'nntp'.
	Transcript showCR:sock nextLine.
	sock buffered:false.

	sock nextPutAll:'HELP'; cr.
	[:exit |
	    |line|

	    line := sock nextLine.
	    line = '.' ifTrue:[exit value:nil].
	    Transcript showCR:line.
	] loopWithExit.
	sock close
									[exEnd]


    example (connect to finger daemon, get users entry):
									[exBegin]
	|sock host entry|

	host := OperatingSystem getHostName.

	sock := Socket newTCPclientToHost:host port:'finger'.
	sock isNil ifTrue:[
	    self warn:'no finger daemon is running'.
	    ^ self
	].
	sock useCRLF:true.
	sock buffered:false.
	sock isNil ifTrue:[
	    Transcript showCR:'cannot connect to local finger daemon'
	] ifFalse:[
	    sock nextPutAll:(OperatingSystem getLoginName).
	    sock cr.

	    entry := sock nextLine.
	    Transcript showCR:entry.

	    sock close
	]
									[exEnd]

    example (connect to an ftp server):
									[exBegin]
	|sock host|

	host := OperatingSystem getHostName.
	sock := Socket newTCPclientToHost:host port:'ftp'.

	sock buffered:false.
	Transcript showCR:sock nextLine.
	sock nextPutAll:('USER ' , 'anonymous'); cr.
	Transcript showCR:sock nextLine.
	sock nextPutAll:('PASS ' , 'fooBar'); cr.
	Transcript showCR:sock nextLine.
	sock nextPutAll:'LIST'; cr.
	Transcript showCR:sock nextLine.
	sock close.

	'dont know enough of the ftp protocol to continue here ...'
									[exEnd]


    example (connect to an snmp server [UDP]):
									[exBegin]
	|sock port|

	sock := Socket newUDP.
	port := Socket portOfService:'snmp'.
	sock connectTo:(OperatingSystem getHostName) port:port.
	sock buffered:false.
	Transcript showCR:'got it'.
	sock close.
									[exEnd]


    example (await connection from a client and read some data):
	|connectSock sock|

	connectSock := Socket newTCPserverAtPort:9998.  
	connectSock isNil ifTrue:[
	    Transcript showCR:'socket setup failed.'.
	] ifFalse:[
	    Transcript showCR:'listen ..'.
	    (connectSock listenFor:5) ifFalse:[
		Transcript showCR:'listen failed.'.
	    ] ifTrue:[
		Transcript showCR:'wait'.
		connectSock readWait.  
		Transcript showCR:'accept'.
		sock := connectSock accept.
		sock isNil ifTrue:[
		    Transcript showCR:'accept failed.'.
		] ifFalse:[
		    sock buffered:false.
		    Transcript showCR:'server: got it'.
		    'can now do transfer via sock'.
		    Transcript showCR:'read'.
		    Transcript showCR:('got: ' , sock nextLine).

		    Transcript showCR:'close'.
		    sock close
		].
		connectSock close.
	    ]
	]


    example (connect to above server and send some data):
	|sock|

	sock := Socket newTCPclientToHost:(OperatingSystem getHostName) port:9998.
	sock isNil ifTrue:[
	    Transcript showCR:'nope'
	] ifFalse:[
	    sock buffered:false.
	    Transcript showCR:'client: got it'.
	    'can now do transfer via sock'.
	    Transcript showCR:'sending <hello>'.
	    sock nextPutLine:'hello'.
	    sock close
	]

    example: UNIX domain socket (await connection from a client and read some data):

	|connectSock sock|

	'/tmp/ud_socket' asFilename remove.
	connectSock := Socket newUNIXserverAt:'/tmp/ud_socket'.  
	connectSock isNil ifTrue:[
	    Transcript showCR:'socket setup failed.'.
	] ifFalse:[
	    Transcript showCR:'listen ..'.
	    (connectSock listenFor:5) ifFalse:[
		Transcript showCR:'listen failed.'.
	    ] ifTrue:[
		Transcript showCR:'wait'.
		connectSock buffered:false.
		connectSock readWait.  
		Transcript showCR:'accept'.
		sock := connectSock accept.
		sock isNil ifTrue:[
		    Transcript showCR:'accept failed.'.
		] ifFalse:[
		    sock buffered:false.
		    Transcript showCR:'server: got it'.
		    'can now do transfer via sock'.
		    Transcript showCR:'read'.
		    Transcript showCR:('got: ' , sock nextLine).

		    Transcript showCR:'close'.
		    sock close
		].
		connectSock close.
	    ]
	]


    example (connect to above server and send some data;
	     Notice, this fails, if above server code is executed in the same ST/X image
		     (at least on LINUX), since the OS does not correctly handle
		     a connect from within an interrupted accept system call
		     On SGI's SVR4, this works ok

	|sock|

	sock := Socket newUNIXclientTo:'/tmp/ud_socket'.
	sock isNil ifTrue:[
	    Transcript showCR:'nope'
	] ifFalse:[
	    sock buffered:false.
	    Transcript showCR:'client: got it'.
	    'can now do transfer via sock'.
	    Transcript showCR:'sending <hello>'.
	    sock nextPutLine:'hello'.
	    sock close
	]


    example: pingWalk (try to ping hosts on the local network)
									[exBegin]
	|myName myAddress list top hosts walkProcess port|

	myName := OperatingSystem getHostName.
	myAddress := Socket ipAddressOfHost:myName.

	port := Socket portOfService:'echo'.
	port isNil ifTrue:[
	    self error:'dont know echo port'.
	    ^ self
	].

	top := StandardSystemView new.
	top label:'PING net walk'.

	list := ScrollableView for:ListView in:top.
	list origin:0.0@0.0 corner:1.0@1.0.

	top openAndWait.

	walkProcess := [
	    |l low hi direction tryHostID dottedName hostName conn addr|

	    l := SortedCollection new.

	    ' only works with type C-net
	      the code below could simply do 1 to:254 do:[:hostID }
	      but, to probe likely hosts earlier, the probing is done
	      ping-pong like around my ip-address (assuming, that other machines
	      have numbers around my own)'.

	    low := hi := (myAddress at:4).
	    direction := 1.

	    [low > 0 or:[hi < 255]] whileTrue:[
		direction > 0 ifTrue:[
		    hi := hi + 1.
		    tryHostID := hi.
		    direction := -1.
		] ifFalse:[
		    low := low - 1.
		    tryHostID := low.
		    direction := 1.
		].
		(tryHostID between:1 and:254) ifTrue:[
		    dottedName := (myAddress at:1) printString
				  , '.' , (myAddress at:2) printString
				  , '.' , (myAddress at:3) printString
				  , '.' , tryHostID printString.

		    top label:'PING net walk - trying ' , dottedName.

		    top windowGroup withCursor:Cursor wait do:[
			conn := Socket newTCPclientToHost:dottedName port:port withTimeout:1000.
			conn notNil ifTrue:[
			    addr := Socket ipAddressOfHost:dottedName.
			    hostName := Socket hostWithIpAddress:addr.
			    hostName isNil ifTrue:[
				hostName :='?'
			    ].
			    l add:(dottedName paddedTo:15 with:Character space) 
				   , ' ' 
				   , (hostName paddedTo:15 with:Character space)
				   , ' up & reachable'.
			    list list:l.
			    conn close.
			]
		    ].
		].
	    ].
	    top label:'PING reachable hosts'.
	] forkAt:(Processor userBackgroundPriority).
	walkProcess name:'ping net walker'.
									[exEnd]


	This example creates a simple UDP server that accepts 
	single packets from anybody and broadcasts them to all 
	clients that have connected so far. 

									[exBegin]
	| socket address buffer msgSize clients |
	clients := Set new.
	address := IPSocketAddress new.
	buffer := String new: 1024.

	socket := self newUDPserverAtPort: 6666.

	Transcript showCR: 'server starting'.

	[
	    [true] whileTrue: [
		(socket readWaitWithTimeoutMs: 200) ifFalse: [
		    msgSize := socket 
			    receiveFrom: address 
			    buffer: buffer 
			    start: 1 
			    for: buffer size.

		    clients add: address copy.
		    clients do: [ :clientAddress | 
			    socket 
				    sendTo: clientAddress 
				    buffer: buffer 
				    start: 1 
				    for: msgSize]]
	    ]
	] valueNowOrOnUnwindDo:[
	    Transcript showCR: 'server shutting down'.
	    socket close
	]
									[exEnd]

   send a datagram to above server:
									[exBegin]

	| socket address buffer host msg |

	host := Dialog
		request: 'What is the name of the server''s host?'
		initialAnswer: 'localhost'.

	socket := self newUDP.

	address := IPSocketAddress hostName: host port: 6666.

	buffer := ByteArray new: 1000.
	[
	    [(msg := Dialog request: 'Say something') isEmpty] whileFalse:[
		| replySize stream |

		socket writeWait.
		stream := buffer writeStream.
		stream nextPutAll: msg.
		socket sendTo:address buffer:buffer start:1 for:stream position.
		socket readWait.

		replySize := socket receiveFrom:address buffer:buffer.
		replySize > 0 ifTrue: [
		    Transcript cr; nextPutAll: 'Server acknowledged: '.
		    Transcript show: ((buffer copyFrom: 1 to: replySize) asString) 
		]
	    ]
	] valueNowOrOnUnwindDo: [socket close].
	Transcript cr
									[exEnd]
"

! !

!Socket class methodsFor:'ST80 instance creation'!

family:domainSymbol type:typeSymbol
    "create a socket for domain and type - ST80 simply uses a different name.
     Domain must be one of the symbols: #inet, #unix, #ns, #appletalk or #ns;
     Type must be #stream, #datagram or #raw

     XXX: currently only the #inet and #unix domains is supported"

    ^ self domain:domainSymbol type:typeSymbol

    "
     Socket family:#inet type:#stream
     Socket family:#inet type:#datagram
     Socket family:#unix type:#stream
    "
! !

!Socket class methodsFor:'ST80 queries'!

getHostname
    "return the computers hostname string"

    ^ OperatingSystem getHostName

    "Created: / 27.2.1998 / 02:32:17 / cg"
!

sockStream
    "return the type code for stream sockets"

    ^ #stream
! !

!Socket class methodsFor:'Signal constants'!

brokenConnectionSignal
    "return the signal used to tell broken connections.
     Since in unix, this is the same as the broken pipe signal,
     return that one.
     (for other Operatingsystems, this may change ..)"

    ^ PipeStream brokenPipeSignal
! !

!Socket class methodsFor:'debugging'!

debug:aBoolean
    "turn on/off internal debugprints.
     This method is for ST/X debugging only and
     may  be removed in later versions"

%{  /* NOCONTEXT */

    __debugging__ = (aBoolean == true);
%}
    "
     Socket debug:true
     Socket debug:false
    "
! !

!Socket class methodsFor:'easy tcp/ip instance creation'!

connectTo:service on:host
    "standard & easy client setup: 
	create new client tcp socket, bind and connect; 
	return the socket.
     The thread block (interruptable), until the connection is 
     established."

    ^ (self new) for:host port:(self portOfService:service).

    "
     Socket connectTo:9995 on:'clam'
     Socket connectTo:'finger' on:'clam'
     Socket connectTo:'ftp' on:'clam'
     Socket connectTo:'nntp' on:(OperatingSystem getEnvironment:'NNTPSERVER')
    "
!

provide:service
    "standard & easy server setup: 
     create a new TCP server socket providing a service."

    |newSock|

    newSock := (self new) for:nil port:(self portOfService:service).
    newSock notNil ifTrue:[
	newSock listenFor:5.
    ].
    ^ newSock

    "
     Socket provide:9995
     (Socket provide:9996) accept
     Socket provide:'nntp'
    "
! !

!Socket class methodsFor:'general instance creation'!

domain:domainSymbol type:type
    "create a socket for domain and type -
     neither any connect nor binding is done.
     Domain must be one of the symbols: 
	#inet, #unix, #appletalk, #decnet, #xns, ...;
     Type must be:
	#stream, #datagram or #raw

     XXX: currently only the #inet domain is supported"

    ^ self new domain:domainSymbol type:type

    "
     Socket domain:#inet type:#stream
     Socket domain:#inet type:#datagram
     Socket domain:#unix type:#stream
     Socket domain:#appletalk type:#stream
     Socket domain:#decnet type:#stream
    "
!

new
    "create a TCP socket"

    ^ super new buffered:false 
!

newTCP
    "create a TCP socket - no binding or other setup is done,
     neither connect nor connect-wait is done."

    ^ self new domain:#inet type:#stream 

    "Socket newUDP"
!

newTCP:aServiceOrNil
    "create a TCP socket for a service -
     neither connect nor connect-wait is done."

    |newSock|

    newSock := self newTCP.
    (newSock notNil and:[aServiceOrNil notNil]) ifTrue:[
	(newSock bindTo:(self portOfService:aServiceOrNil) address:nil) ifFalse:[
	    ^ nil
	]
    ].
    ^ newSock


    "Socket newTCP:'nntp'"
    "Socket newTCP:9995"
!

newTCPclientToAddress:aHostAddress port:aService
    "create a new TCP client socket connecting to a service.
     Return a socket instance if ok, nil on failure.
     Block until a connection is established (but only the current thread;
     not the whole smalltalk). 
     See also: #newTCPclientToAddress:port:withTimeout:"

    ^ self newTCPclientToAddress:aHostAddress port:aService withTimeout:nil
!

newTCPclientToAddress:aHostAddress port:aService withTimeout:millis
    "create a new TCP client socket connecting to a service.
     Return a socket instance if ok, nil on failure.
     If the millis arg is nonNil, stop trying to connect after that many milliseconds
     and return nil."

    ^ self newTCPclientToHost:aHostAddress port:aService withTimeout:millis
!

newTCPclientToHost:hostname port:aService
    "create a new TCP client socket connecting to a service.
     Return a socket instance if ok, nil on failure.
     Block until a connection is established (but only the current thread;
     not the whole smalltalk). 
     See also: #newTCPclientToHost:port:withTimeout:"

    ^ self newTCPclientToHost:hostname port:aService withTimeout:nil

    "
      Socket newTCPclientToHost:'localhost' port:'nntp'
    "

    "Created: 31.10.1995 / 18:54:11 / cg"
!

newTCPclientToHost:hostname port:aService withTimeout:millis
    "create a new TCP client socket connecting to a service.
     Return a socket instance if ok, nil on failure.
     If the millis arg is nonNil, stop trying to connect after that many milliseconds
     and return nil.."

    |newSock|

    newSock := self newTCP.
    newSock notNil ifTrue:[
	(newSock connectTo:hostname 
		 port:(self portOfService:aService protocol:'tcp') 
		 withTimeout:millis
	) ifFalse:[
	    newSock close.
	    ^ nil
	]
    ].
    ^ newSock
"
same as:
    ^ (self new) for:hostname port:(self portOfService:aPort).
"
    "
      Socket newTCPclientToHost:'slsv6bt' port:'nntp'
      Socket newTCPclientToHost:'localhost' port:'nntp' withTimeout:1000
    "

    "Modified: / 16.1.1998 / 09:47:06 / stefan"
!

newTCPserverAtAnonymousPort
    "create a new TCP server socket providing service on
     a new anonymous port. The portNr is assigned by the OS."

    ^ self newTCPserverAtPort:0

!

newTCPserverAtPort:aService
    "create a new TCP server socket providing service."

    |newSock|

    newSock := self newTCP.
    newSock notNil ifTrue:[
	(newSock bindTo:(self portOfService:aService) address:nil) ifFalse:[
	    ^ nil
	]
    ].
    ^ newSock
"
same as:
    ^ (self new) for:nil port:aPort
"
!

newUDP
    "create a UDP socket - no binding or other setup is done,
     neither connect nor connect-wait is done."

    ^ self new domain:#inet type:#datagram

    "Socket newUDP"
!

newUDP:aServiceOrNil
    "create a UDP socket for a service -
     neither connect nor connect-wait is done."

    |newSock|

    newSock := self newUDP.
    (newSock notNil and:[aServiceOrNil notNil]) ifTrue:[
	(newSock bindTo:(self portOfService:aServiceOrNil) address:nil) ifFalse:[
	    ^ nil
	]
    ].
    ^ newSock

    "Socket newUDP:nil"
!

newUDPserverAtPort:aService
    "create a new UDP server socket providing service."

    |newSock|

    newSock := self newUDP.
    newSock notNil ifTrue:[
	(newSock bindTo:(self portOfService:aService) address:nil) ifFalse:[
	    ^ nil
	]
    ].
    ^ newSock
"
same as:
    ^ (self new) for:nil udpPort:aPort
"
!

newUNIX
    "create a UNIX domain socket - no binding or other setup is done,
     neither connect nor connect-wait is done.
     If the system does not support unix domain sockets (i.e. VMS or MSDOS),
     return nil."

    ^ self new domain:#unix type:#stream 

    "
     Socket newUNIX
    "
!

newUNIXclientTo:pathName 
    "create a new UNIX client socket connecting to a pathname.
     Return a socket instance if ok, nil on failure.
     Block until a connection is established (but only the current thread;
     not the whole smalltalk). 
     If the system does not support unix domain sockets (i.e. VMS or MSDOS),
     return nil.
     See also: #newUNIXclientTo:withTimeout:"

    ^ self newUNIXclientTo:pathName withTimeout:nil

!

newUNIXclientTo:pathName withTimeout:millis
    "create a new UNIX client socket connecting to a pathname.
     Return a socket instance if ok, nil on failure.
     If the millis arg is nonNil, stop trying to connect after that many milliseconds
     and return nil.
     If the system does not support unix domain sockets (i.e. VMS or MSDOS),
     return nil."

    |newSock|

    newSock := self newUNIX.
    newSock notNil ifTrue:[
	(newSock connectTo:pathName port:nil withTimeout:millis) ifFalse:[
	    newSock close.
	    ^ nil
	]
    ].
    ^ newSock

    "
     |s|

     s := Socket newUNIXclientTo:'/tmp/foo'
    "
!

newUNIXserverAt:pathName
    "create a new UNIX server socket providing service at a pathname.
     If the system does not support unix domain sockets (i.e. VMS or MSDOS),
     return nil."

    |newSock|

    newSock := self newUNIX.
    newSock notNil ifTrue:[
	(newSock bindTo:pathName address:nil) ifFalse:[
	    ^ nil
	]
    ].
    ^ newSock

    "
     |s s2|

     s := Socket newUNIXserverAt:'/tmp/foo'.
     s listenFor:5.
     s2 := s accept.
    "
! !

!Socket class methodsFor:'host queries'!

appletalkAddressOfHost:aHostName
    "return the APPLETALK address for a hostname as a byteArray,
     where the network bytes come first (no matter what the local byteorder is)
     followed by the node byte.
     If the host is unknown, return nil.
     This is the reverse operation to #hostWithAppletalkAddress:.
     WARNING: untested code - I have no appletalk to test this."

%{
#if !defined(NO_SOCKET) && defined(AF_APPLETALK)
    struct sockaddr_at sa;
    struct hostent *hp ;
    long addr;
    OBJ rslt;

    sa.sat_family = -1;

    if (__isString(aHostName)) {
	bzero(&sa, sizeof(sa)) ;

	/* do we know the host's address? */
	GETHOSTBYNAME(hp, __stringVal(aHostName))
	if (hp == NULL) {
	    DBGPRINTF(("SOCKET: unknown appletalk host: %s\n", __stringVal(aHostName)));
	    RETURN ( nil );
	}
	bcopy(hp->h_addr, (char *) &sa.sat_addr, hp->h_length) ;
	sa.sat_family = hp->h_addrtype;
    }

    /* if the addressing family is not AF_APPLETALK, Return nil */
    if (sa.sat_family != AF_APPLETALK) {
	DBGPRINTF(("SOCKET: not an appletalk host\n"));
	RETURN ( nil );
    }

    sa.sat_addr.s_net = ntohs(sa.sat_addr.s_net);    
    rslt = __BYTEARRAY_NEW_INT(3);
    if (rslt != nil) {
	__ByteArrayInstPtr(rslt)->ba_element[0] = (sa.sat_addr.s_net >> 8) & 0xFF;
	__ByteArrayInstPtr(rslt)->ba_element[1] = (sa.sat_addr.s_net) & 0xFF;
	__ByteArrayInstPtr(rslt)->ba_element[2] = (sa.sat_addr.s_node) & 0xFF;
       RETURN (rslt);
    }
#endif
%}.
    ^ nil

!

hostWithAppletalkAddress:anAddress
    "return the hostname for an APPLETALK address.
     The address is supposed to be a byteArray consisting of 3 bytes,
     the network bytes come first (no matter what the local byteorder is).
     The last byte is the node number.
     Nil is returned for an unknown host or if its not an appletalk host.
     This is is the reverse operation to #appletalkAddressOfHost:.
     WARNING: untested code - I have no appletalk to test this."

    |b1 b2 b3 b4|

    b1 := anAddress at:1. "/ net-hi
    b2 := anAddress at:2. "/ net-low
    b3 := anAddress at:3. "/ node
%{
#if !defined(NO_SOCKET) && defined(AF_APPLETALK)
    struct sockaddr_at sa ;
    struct hostent *hp ;

    sa.sat_family = -1;

    if (__bothSmallInteger(b1, b2) && __bothSmallInteger(b3, b4)) {
	bzero(&sa, sizeof(sa)) ;

	sa.sat_addr.s_net = _intVal(b1) & 0xFF;
	sa.sat_addr.s_net = (sa.sat_addr.s_net << 8) | (_intVal(b2) & 0xFF);
	sa.sat_addr.s_net = htons(sa.sat_addr.s_net);    
	sa.sat_addr.s_node = _intVal(b3) & 0xFF;
	sa.sat_family = AF_APPLETALK;

	/* do we know the host's address? */
	GETHOSTBYADDR(hp, (char *) &sa.sat_addr, sizeof(sa.sat_addr), AF_APPLETALK);
	if (hp != NULL) {
	    sa.sat_family = hp->h_addrtype;
	} else {
	    DBGPRINTF(("SOCKET: unknown appletalk address: %d.%d.%d.%d\n", 
		       _intVal(b1), _intVal(b2), _intVal(b3)));
	}
    }

    /* if the addressing family is not AF_APPLETALK, Return nil */
    if (sa.sat_family != AF_APPLETALK) {
	DBGPRINTF(("SOCKET: not an appletalk host\n"));
	RETURN ( nil );
    }

    if (hp != NULL) {
	RETURN (__MKSTRING(hp->h_name));
    }
#endif
    RETURN (nil);
%}.
    "
     Socket appletalkAddressOfHost:'clam'
     Socket hostWithAppletalkAddress:#[1 2 3]  
     "
!

hostWithIpAddress:anAddress
    "return the hostname for an IP (internet-) address.
     The address is supposed to be a byteArray consisting of 4 bytes,
     the network bytes come first (no matter what the local byteorder is).
     Nil is returned for an unknown host or if its not an internet host.
     This is the reverse operation to #ipAddressOfHost:."

    |b1 b2 b3 b4|

    b1 := anAddress at:1.
    b2 := anAddress at:2.
    b3 := anAddress at:3.
    b4 := anAddress at:4.
%{
#if !defined(NO_SOCKET) && defined(AF_INET)
    struct sockaddr_in sa ;
    struct hostent *hp ;

    sa.sin_family = -1;
    if (__bothSmallInteger(b1, b2) && __bothSmallInteger(b3, b4)) {
        bzero(&sa, sizeof(sa)) ;
        sa.sin_addr.s_addr = _intVal(b1) & 0xFF;
        sa.sin_addr.s_addr = (sa.sin_addr.s_addr << 8) | (_intVal(b2) & 0xFF);
        sa.sin_addr.s_addr = (sa.sin_addr.s_addr << 8) | (_intVal(b3) & 0xFF);
        sa.sin_addr.s_addr = (sa.sin_addr.s_addr << 8) | (_intVal(b4) & 0xFF);
        sa.sin_addr.s_addr = htonl(sa.sin_addr.s_addr);    
        sa.sin_family = AF_INET;
        /* do we know the host's address? */
        GETHOSTBYADDR(hp, (char *) &sa.sin_addr, sizeof(sa.sin_addr), AF_INET);
        
        if (hp == NULL) {
            DBGPRINTF(("SOCKET: unknown ip address: %d.%d.%d.%d\n", 
                       _intVal(b1), _intVal(b2), _intVal(b3), _intVal(b4)));
        } else {
            sa.sin_family = hp->h_addrtype;
        }
    }

    /* if the addressing family is not AF_INET, Return nil */
    if (sa.sin_family != AF_INET) {
        RETURN ( nil );
    }

    if (hp != NULL) {
        RETURN (__MKSTRING(hp->h_name));
    }

    /*
     * Return it in dot-notation
     */
    RETURN (__MKSTRING(inet_ntoa(sa.sin_addr)));
#else
    RETURN (nil);
#endif
%}

    "
     Socket ipAddressOfHost:'clam'
     Socket hostWithIpAddress:(Socket ipAddressOfHost:'clam') 
     Socket ipAddressOfHost:'porty'
     Socket hostWithIpAddress:(Socket ipAddressOfHost:'porty') 
     Socket hostWithIpAddress:#[1 2 3 4]  
     Socket hostWithIpAddress:#[127 0 0 1]  
     Socket hostWithIpAddress:(Socket ipAddressOfHost:'1.2.3.4')  
     "
!

hostWithIpV6Address:anAddress
    "return the hostname for an IPv6 (internet-) address.
     The address is supposed to be a byteArray consisting ??? bytes,
     the network bytes come first (no matter what the local byteorder is).
     Nil is returned for an unknown host or if its not an internet host.
     This is the reverse operation to #ipV6AddressOfHost:."

%{
#if !defined(NO_SOCKET) && defined(AF_INET6)
    struct sockaddr_in6 sa ;
    struct hostent *hp ;

    sa.sin6_family = -1;
    if (__isByteArray(anAddress)) {
	bzero(&sa, sizeof(sa)) ;
	if (__byteArraySize(anAddress) <= sizeof(sa.sin6_addr.s6_addr))
	    goto bad;
	bcopy(sa.sin6_addr.s6_addr, __ByteArrayInstPtr(anAddress)->ba_element, sizeof(sa.sin6_addr.s6_addr));

	sa.sin6_family = AF_INET6;
	/* do we know the host's address? */
	GETHOSTBYADDR(hp, (char *) &sa.sin6_addr, sizeof(sa.sin6_addr), AF_INET6);
	if (hp == NULL) {
	    DBGPRINTF(("SOCKET: unknown ipv6 address: %d.%d.%d.%d...\n", 
		       sa.sin6_addr.s6_addr[0], 
		       sa.sin6_addr.s6_addr[1], 
		       sa.sin6_addr.s6_addr[2],
		       sa.sin6_addr.s6_addr[3] ));
	} else {
	    sa.sin6_family = hp->h_addrtype;
	}
    }
    bad: ;
    /* if the addressing family is not AF_INET6, Return nil */
    if (sa.sin6_family != AF_INET6) {
	DBGPRINTF(("SOCKET: not an ipv6 host\n")); 
	RETURN ( nil );
    }

    if (hp != NULL) {
	RETURN (__MKSTRING(hp->h_name));
    }

    /*
     * Return it in dot-notation
     */
    RETURN (__MKSTRING(inet_ntoa(sa.sin6_addr)));
#else
    RETURN (nil);
#endif
%}

    "
     Socket ipV6AddressOfHost:'clam'
     Socket hostWithIpV6Address:(Socket ipAddressOfHost:'clam') 
     Socket ipV6AddressOfHost:'porty'
     Socket hostWithIpV6Address:(Socket ipAddressOfHost:'porty') 
     Socket hostWithIpV6Address:#[1 2 3 4 5 6 7 8 9 10 11 12 13 14]  
     "
!

ipAddressOfHost:aHostName
    "return the IP (internet-) number for a hostname as a byteArray,
     where the network bytes come first (no matter what the cpus byteOrder is).
     If the host is unknown, return nil.
     This is the reverse operation to #hostWithIpAddress:."

%{
#if !defined(NO_SOCKET) && defined(AF_INET)
    struct sockaddr_in sa ;
    struct hostent *hp ;
    long addr;
    OBJ rslt;

    sa.sin_family = -1;

    if (__isString(aHostName)) {
	bzero(&sa, sizeof(sa)) ;
	if ((addr = inet_addr((char *) __stringVal(aHostName))) != -1) {
	    /* is Internet addr in octet notation */
	    bcopy(&addr, (char *) &sa.sin_addr, sizeof(addr)); 
	    sa.sin_family = AF_INET;
	} else {
	    /* do we know the host's address? */
	    GETHOSTBYNAME(hp, __stringVal(aHostName))
	    if (hp == NULL) {
		DBGPRINTF(("SOCKET: unknown ip host: %s\n", __stringVal(aHostName)));
		RETURN ( nil );
	    }
	    bcopy(hp->h_addr, (char *) &sa.sin_addr, hp->h_length) ;
	    sa.sin_family = hp->h_addrtype;
	}
    }

    /* if the addressing family is not AF_INET, Return nil */
    if (sa.sin_family != AF_INET) {
	DBGPRINTF(("SOCKET: not an ip host\n"));
	RETURN ( nil );
    }

    sa.sin_addr.s_addr = ntohl(sa.sin_addr.s_addr);    
    rslt = __BYTEARRAY_NEW_INT(4);
    if (rslt != nil) {
	__ByteArrayInstPtr(rslt)->ba_element[0] = (sa.sin_addr.s_addr >> 24) & 0xFF;
	__ByteArrayInstPtr(rslt)->ba_element[1] = (sa.sin_addr.s_addr >> 16) & 0xFF;
	__ByteArrayInstPtr(rslt)->ba_element[2] = (sa.sin_addr.s_addr >> 8) & 0xFF;
	__ByteArrayInstPtr(rslt)->ba_element[3] = (sa.sin_addr.s_addr >> 0) & 0xFF;
       RETURN (rslt);
    }
#endif
%}.
    ^ nil

    "
     Socket ipAddressOfHost:'localhost' 
     Socket ipAddressOfHost:'exept'    
     Socket ipAddressOfHost:'1.2.3.4'    
     Socket ipAddressOfHost:'193.15.16.17'    
     Socket ipAddressOfHost:'josef'     
     Socket ipAddressOfHost:'styx.com'  
     Socket hostWithIpAddress:(Socket ipAddressOfHost:'localhost') 
     Socket ipAddressOfHost:(Socket hostWithIpAddress:'127.0.0.1') 
    "
!

ipV6AddressOfHost:aHostName
    "return the IPv6 (internet-) number for a hostname as a byteArray,
     where the network bytes come first (no matter what the cpus byteOrder is).
     If the host is unknown, return nil.
     This is the reverse operation to #hostWithIpV6Address:."

%{
#if !defined(NO_SOCKET) && defined(AF_INET6)
    struct sockaddr_in6 sa;
    struct hostent *hp ;
    long addr;
    OBJ rslt;

    sa.sin6_family = -1;

    if (__isString(aHostName)) {
	bzero(&sa, sizeof(sa)) ;
#if 0
	if ((addr = inet_addr((char *) __stringVal(aHostName))) != -1) {
	    /* is Internet addr in octet notation */
	    bcopy(&addr, (char *) &sa.sin_addr, sizeof(addr)); 
	    sa.sin_family = AF_INET;
	} else 
#endif
	{
	    /* do we know the host's address? */
	    GETHOSTBYNAME(hp, __stringVal(aHostName))
	    if (hp == NULL) {
		DBGPRINTF(("SOCKET: unknown host: %s\n", __stringVal(aHostName)));
		RETURN ( nil );
	    }
	    bcopy(hp->h_addr, (char *) &sa.sin6_addr, hp->h_length) ;
	    sa.sin6_family = hp->h_addrtype;
	}
    }

    /* if the addressing family is not AF_INET, Return nil */
    if (sa.sin6_family != AF_INET) {
	DBGPRINTF(("SOCKET: not an ipv6 host\n"));
	RETURN ( nil );
    }

    rslt = __BYTEARRAY_NEW_INT(hp->h_length);
    if (rslt != nil) {
	bcopy(sa.sin6_addr.s6_addr, __ByteArrayInstPtr(rslt)->ba_element, hp->h_length);
       RETURN (rslt);
    }
#endif
%}.
    ^ nil

    "
     Socket ipV6AddressOfHost:'localhost' 
     Socket ipV6AddressOfHost:'exept'    
     Socket ipV6AddressOfHost:'1.2.3.4.5.6.7.8.9.10.11.12.13.14.15.16'    
     Socket ipV6AddressOfHost:'193.15.16.17'    
     Socket ipV6AddressOfHost:'josef'     
     Socket ipV6AddressOfHost:'styx.com'  
     Socket hostWithIpV6Address:(Socket ipV6AddressOfHost:'localhost') 
     Socket ipV6AddressOfHost:(Socket hostV6WithIpAddress:'127.0.0.1') 
    "
! !

!Socket class methodsFor:'queries'!

domainOfProtocol:aProtocol
    "given a protocols name (i.e. tcp, udp etc) return the domain.
     This method needs more ... - or is there a way to get this from the system ?"

    "
     tcp/ip stuff
    "
    (aProtocol = 'tcp') ifTrue:[^ #inet].
    (aProtocol = 'udp') ifTrue:[^ #inet].
    (aProtocol = 'ip')  ifTrue:[^ #inet].
    "
     unix domain
    "
    (aProtocol = 'ud')  ifTrue:[^ #unix].

    "
     add x25 stuff (if any) here ...
    "
    "
     add appletalk stuff (if any) here ...
    "
    "
     add other stuff (if any) here ...
    "
    ^ nil

    "
     Socket domainOfProtocol:'tcp'
     Socket domainOfProtocol:'ucp'
     Socket domainOfProtocol:(Socket protocolOfService:'nntp')
     Socket domainOfProtocol:(Socket protocolOfService:'echo')
    "
!

networkLongOrderIsMSB
    "return true, if the network-byte-order of longs is MSB.
     To be used as in:
	'aStream nextPutLong:someValue MSB:(Socket networkLongOrderIsMSB)'."

%{  /* NOCONTEXT */
#ifndef NO_SOCKET
    /*
     * mhmh - do c-compilers optimize this away ?
     */
    if (htonl(0x76543210) == 0x76543210) {
	RETURN (true);
    }
#endif
%}.
    ^ false

    "
     Socket networkLongOrderIsMSB
    "
!

networkShortOrderIsMSB
    "return true, if the network-byte-order of shorts is MSB.
     To be used as in:
	'aStream nextPutShort:someValue MSB:(Socket networkShortOrderIsMSB)'."

%{  /* NOCONTEXT */
#ifndef NO_SOCKET
    /*
     * mhmh - do c-compilers optimize this away ?
     */
    if (htons(0x3210) == 0x3210) {
	RETURN (true);
    }
#endif
%}.
    ^ false

    "
     Socket networkShortOrderIsMSB
    "
!

portOfService:aNameOrNumber
    "returns the port-number for a given IP-service
     or nil if no such service exists;
     - used to convert service names to portNumbers"

    ^ self portOfService:aNameOrNumber protocol:nil

    "
     Socket portOfService:'finger'
     Socket portOfService:'nntp'  
     Socket portOfService:'echo' 
     Socket portOfService:'snmp' 
    "
!

portOfService:aNameOrNumber protocol:aProtocol
    "returns the port-number for a given IP-service
     or nil if no such service exists;
     - used to convert service names to portNumbers"

%{ /* NOCONTEXT */
#ifndef NO_SOCKET
    struct servent *servent = NULL;
    char *protocol;
    int tryBoth = 0;
    short portNo;

    if (__isSmallInteger(aNameOrNumber)) {
	RETURN ( aNameOrNumber );
    }

    if (__isString(aProtocol)) {
	protocol = (char *)__stringVal(aProtocol);
    } else {
	protocol = "tcp";
	tryBoth = 1;
    }

    if (__isString(aNameOrNumber) || __isSymbol(aNameOrNumber)) {
	servent = getservbyname((char *) __stringVal(aNameOrNumber), protocol);
	if (servent != NULL) {
	    RETURN ( __MKSMALLINT(ntohs(servent->s_port)) );
	}
	if (tryBoth) {
	    servent = getservbyname((char *) __stringVal(aNameOrNumber), "udp");
	    if (servent != NULL) {
		RETURN ( __MKSMALLINT(ntohs(servent->s_port)) );
	    }
	}
	RETURN ( nil );
    }
#endif
    RETURN ( nil );
%}
    "
     Socket portOfService:'echo' protocol:'udp'
     Socket portOfService:'echo' protocol:'tcp'
    "
!

protocolOfService:aNameOrNumber
    "returns the protocol (as string) for a given IP-service
     or nil if no such service exists."
%{
#ifndef NO_SOCKET
    struct servent *servent = NULL;
    short portNo;

    if (__isSmallInteger(aNameOrNumber)) {
	portNo = __intVal(aNameOrNumber);
	servent = getservbyport(htons(portNo), "tcp") ;
	if (servent == NULL) {
	    servent = getservbyport(htons(portNo), "udp") ;
	    if (servent == NULL) {
		RETURN ( nil );
	    }
	}
    } else {
	if (__isString(aNameOrNumber)) {
	    servent = getservbyname((char *) __stringVal(aNameOrNumber), "tcp");
	    if (servent == NULL) {
		servent = getservbyname((char *) __stringVal(aNameOrNumber), "udp");
		if (servent == NULL) {
		    RETURN ( nil );
		}
	    }
	}
    }
    if (servent) {
	RETURN ( __MKSTRING(servent->s_proto) );
    }
#endif
    RETURN ( nil );
%}
    "
     Socket protocolOfService:'finger' 
     Socket protocolOfService:'nntp'  
     Socket protocolOfService:'xxx'
     Socket protocolOfService:79
     Socket protocolOfService:'snmp' 
    "
!

supportedProtocolFamilies
    "return a collection of supported protocol families.
     This list specifies what the Socket class supports -
     socket creation may still fail, if your system was built
     without it."

    |list hasIt|

    list := OrderedCollection new.

%{
#ifdef AF_INET
%}.
    list add:#inet.
%{
#endif
%}.

%{
#ifdef AF_UNIX
%}.
    list add:#unix.
%{
#endif
%}.

%{
#ifdef AF_INET6
%}.
    list add:#inet6.   "/ internet v6
%{
#endif
%}.

%{
#ifdef AF_APPLETALK
%}.
    list add:#appletalk.  "/ appletalk
%{
#endif
%}.

%{
#ifdef AF_DECnet
%}.
    list add:#decnet.  "/ dec net
%{
#endif
%}.

%{
#ifdef AF_NS
%}.
    list add:#xns.     "/ Xerox XNS
%{
#endif
%}.

%{
#ifdef AF_X25
%}.
    list add:#x25.     "/ X.25
%{
#endif
%}.

%{
#ifdef AF_SNA
%}.
    list add:#sna.     "/ IBM SNA
%{
#endif
%}.

%{
#ifdef AF_RAW
%}.
    list add:#raw.     "/ ?? RAW packets
%{
#endif
%}.

%{
#ifdef AF_ISO
%}.
    list add:#iso.     "/ ??
%{
#endif
%}.

%{
#ifdef AF_NETBIOS
%}.
    list add:#netbios. "/ ??
%{
#endif
%}.

%{
#ifdef AF_IPX
%}.
    list add:#ipx.     "/ Novell IPX
%{
#endif
%}.

%{
#ifdef AF_AX25
%}.
    list add:#ax25.    "/ Amateur Radio AX.25
%{
#endif
%}.

%{
#ifdef AF_NETROM
%}.
    list add:#netrom.  "/ Amateur Radio NET/ROM
%{
#endif
%}.

%{
#ifdef AF_BRIDGE
%}.
    list add:#bridge.  "/ multiprotocol bridge
%{
#endif
%}.

%{
#ifdef AF_BSC
%}.
    list add:#bsc.     "/ BISYNC 2780/3780
%{
#endif
%}.

%{
#ifdef AF_ROSE
%}.
    list add:#rose.    "/ Amateur Radio X.25 PLP
%{
#endif
%}.


    ^ list

    "
     Socket supportedProtocolFamilies
    "
!

typeOfProtocol:aProtocol
    "given a protocols name (i.e. tcp, udp etc) return the connection type.
     This method needs more ... - or is there a way to get this from the system ?"

    (aProtocol = 'tcp') ifTrue:[^ #stream].
    (aProtocol = 'udp') ifTrue:[^ #datagram].
    (aProtocol = 'ip')  ifTrue:[^ #raw].
    "
     unix domain
    "
    (aProtocol = 'ud')  ifTrue:[^ #stream].
    "
     add x25 stuff (if any) here ...
    "
    "
     add appletalk stuff (if any) here ...
    "
    "
     add other stuff (if any) here ...
    "
    ^ nil

    "
     Socket typeOfProtocol:'tcp'
     Socket typeOfProtocol:'ucp'
     Socket typeOfProtocol:(Socket protocolOfService:'nntp')
     Socket typeOfProtocol:(Socket protocolOfService:'echo')
    "
! !

!Socket methodsFor:'ST-80 compatibility'!

errorReporter
    "ST-80 mimicry."

    ^ self
!

notReadySignal
    "ST-80 mimicry.
     for now - this is not yet raised"

    ^ Signal new
!

readAppendStream
    "ST-80 mimicry.
     In ST-80, socket is not a stream, but referes to one.
     ST-80 code therefore uses 'Socket readWriteStream' to access
     the actual stream. 
     In ST/X, sockets inherit from stream, so
     this method returns the receiver, for transparency"

    ^ self
!

readStream
    "ST-80 mimicry.
     In ST-80, socket is not a stream, but referes to one.
     ST-80 code therefore uses 'Socket readStream' to access
     the actual stream. 
     In ST/X, sockets inherit from stream, so
     this method returns the receiver, for transparency"

    ^ self

    "Created: 24.1.1997 / 23:52:57 / cg"
!

shutdown:how
    "ST-80 compatibility"

    self shutDown
!

writeStream
    "ST-80 mimicry.
     In ST-80, socket is not a stream, but referes to one.
     ST-80 code therefore uses 'Socket writeStream' to access
     the actual stream. 
     In ST/X, sockets inherit from stream, so
     this method returns the receiver, for transparency"

    ^ self

    "Created: 24.1.1997 / 10:34:35 / cg"
    "Modified: 24.1.1997 / 23:52:52 / cg"
! !

!Socket methodsFor:'Squeak compatibility'!

peerName
    "return my peer (i.e. ipAddr + port);
     May return nil if not yet setup completely."

    ^ self getPeer
! !

!Socket methodsFor:'datagram transmission'!

receiveFrom:anAddressBuffer buffer:aDataBuffer
    "receive datagramm data - put address of originating host into
     anAddressBuffer, data into aBuffer. 
     Both must be ByteArray-like. The addressBuffer must
     provide space for a valid address for my domain (i.e. for inet, a 4-byte byteArray).
     Return the number of bytes received, or a negative number on error.
     On error, the unix error code is left in the lastErrorNumber
     instance variable."

    ^ self receiveFrom:anAddressBuffer buffer:aDataBuffer start:1 for:(aDataBuffer size)
!

receiveFrom:anAddressBuffer buffer:aDataBuffer start:startIndex for:nBytes
    "receive datagramm data - put address of originating host into
     anAddressBuffer, data into aBuffer. For ST-80 compatibility,
     the addressBuffer may be a non-ByteArray; then, it must understand
     the addressBytes-message (i.e. be a SocketAddress instance).
     Return the number of bytes received, or a negative number on error.
     On error, the unix error code is left in the lastErrorNumber
     instance variable.
     The thread blocks until data arrives - you may want to wait before
     receiving, using #readWait or #readWaitWithTimeout:."


    |addrBytes addrLen nReceived|

    addrBytes := ByteArray new:100.
%{
#ifndef NO_SOCKET
    OBJ oClass, myDomain;
    OBJ fp = __INST(filePointer);
    int nInstVars, nInstBytes, objSize;
    int sock;
    union sockaddr_u sa;
    int alen;
    int n;
    char *cp;
    int flags = 0;

    if (fp != nil) {
	sock = fileno(__FILEVal(fp));

	oClass = __Class(aDataBuffer);
	switch (_intVal(_ClassInstPtr(oClass)->c_flags) & ARRAYMASK) {
	    case BYTEARRAY:
	    case WORDARRAY:
	    case SWORDARRAY:
	    case LONGARRAY:
	    case SLONGARRAY:
	    case FLOATARRAY:
	    case DOUBLEARRAY:
		break;
	    default:
		goto bad;
	}

	nInstVars = _intVal(_ClassInstPtr(oClass)->c_ninstvars);
	nInstBytes = OHDR_SIZE + nInstVars * sizeof(OBJ);
	objSize = _Size(aDataBuffer) - nInstBytes;
	cp = (char *)__InstPtr(aDataBuffer) + nInstBytes;
	if (__isSmallInteger(startIndex)) {
	    cp += __intVal(startIndex);
	    objSize -= __intVal(startIndex);
	}
	if (__isSmallInteger(nBytes)) {
	    if (__intVal(nBytes) < objSize) {
		objSize = __intVal(nBytes);
	    }
	}

	__BEGIN_INTERRUPTABLE__
	do {
	    if (addrBytes == nil) {
		n = recvfrom(sock, cp, objSize, flags, (struct sockaddr *) 0, 0);
	    } else {
		n = recvfrom(sock, cp, objSize, flags, (struct sockaddr *) &sa, &alen);
	    }
	} while ((n < 0) && (errno == EINTR));
	__END_INTERRUPTABLE__

	if (n >= 0) {
	    if (addrBytes != nil) {
		oClass = __Class(addrBytes);
		if ((_intVal(_ClassInstPtr(oClass)->c_flags) & ARRAYMASK) != BYTEARRAY) 
		    goto bad;
		nInstVars = _intVal(_ClassInstPtr(oClass)->c_ninstvars);
		nInstBytes = OHDR_SIZE + nInstVars * sizeof(OBJ);
		objSize = _Size(addrBytes) - nInstBytes;
		cp = (char *)__InstPtr(addrBytes) + nInstBytes;
		if (objSize < alen) 
		    goto bad;

		myDomain = __INST(domain);

		/*
		 * extract the datagrams address
		 */
# ifdef AF_INET
		if (myDomain == @symbol(inet)) {
		    if (objSize < 4) 
			goto bad;
		    cp[0] = (sa.in.sin_addr.s_addr >> 24) & 0xFF;
		    cp[2] = (sa.in.sin_addr.s_addr >> 16) & 0xFF;
		    cp[3] = (sa.in.sin_addr.s_addr >> 8) & 0xFF;
		    cp[4] = (sa.in.sin_addr.s_addr >> 0) & 0xFF;
		    alen = 4;
		}
# endif /* AF_INET */

# ifdef AF_INET6
		if (myDomain == @symbol(inet6)) {
		    if (objSize < sizeof(sa.in6.sin6_addr.s6_addr)) 
			goto bad;
		    bcopy(sa.in6.sin6_addr.s6_addr, cp, sizeof(sa.in6.sin6_addr.s6_addr));
		    alen = sizeof(sa.in6.sin6_addr.s6_addr);
		}
# endif /* AF_INET6 */

# ifdef AF_APPLETALK
		if (myDomain == @symbol(appletalk)) {
		    if (objSize < 3) 
			goto bad;
		    cp[0] = (sa.at.sat_addr.s_net >> 8) & 0xFF;
		    cp[2] = (sa.at.sat_addr.s_net) & 0xFF;
		    cp[3] = (sa.at.sat_addr.s_node) & 0xFF;
		    alen = 3;
		}
# endif /* AF_APPLETALK */

		/*
		 * XXXX add addressing stuff for other domains here ...
		 */
# ifdef AF_X25
		if (myDomain == @symbol(x25)) {
		}
# endif

# ifdef AF_AX25
		if (myDomain == @symbol(ax25)) {
		}
# endif

# ifdef AF_NS
		if ((myDomain == @symbol(ns)) 
		 || (myDomain == @symbol(xns))) {
		}
# endif

# ifdef AF_SNA
		if (myDomain == @symbol(sna)) {
		}
# endif

# ifdef AF_RAW
		if (myDomain == @symbol(raw)) {
		}
# endif

# ifdef AF_ISO
		if (myDomain == @symbol(iso)) {
		}
# endif

# ifdef AF_DECnet
		if (myDomain == @symbol(decnet)) {
		}
# endif

# ifdef AF_NETBIOS
		if (myDomain == @symbol(netbios)) {
		}
# endif

# ifdef AF_IPX
		if (myDomain == @symbol(ipx)) {
		}
# endif

# ifdef AF_BRIDGE
		if (myDomain == @symbol(bridge)) {
		}
# endif

# ifdef AF_BSC
		if (myDomain == @symbol(bsc)) {
		}
# endif

# ifdef AF_ROSE
		if (myDomain == @symbol(rose)) {
		}
# endif

# if defined(AF_CCITT) && (AF_CCITT != AF_X25)
		if (myDomain == @symbol(ccitt)) {
		}
# endif

		addrLen = __MKSMALLINT(alen);
	    }
	}
	if (n < 0) {
	    __INST(lastErrorNumber) = __MKSMALLINT(errno);
	}
	nReceived = __MKSMALLINT(n);
    }
#endif
bad: ;
%}.
    nReceived notNil ifTrue:[
	nReceived < 0 ifTrue:[
	    'Socket [warning]: ' infoPrint.
	    (OperatingSystem errorTextForNumber:lastErrorNumber) infoPrintCR.
	].
	addrLen notNil ifTrue:[
	    anAddressBuffer class isBytes ifTrue:[
		"/ can be a ByteArray for ST/X compatibility
		anAddressBuffer replaceFrom:1 to:addrLen with:addrBytes
	    ] ifFalse:[
		"/ can be a SocketAddress for ST-80 compatibility
		anAddressBuffer hostAddress:(addrBytes copyTo:addrLen)
	    ].
	].
	^ nReceived
    ].
    "
     arrive here if you try to receive into an invalid buffer
     (i.e. not ByteArray-like), 
     or if the addressBuffer is nonNil AND not a ByteArray/String 
     or if the addressBuffer is nonNil AND too small.
    "
    self primitiveFailed
!

sendTo:anAddressBuffer buffer:buffer
    "send datagramm data - fetch address of destination host from
     anAddressBuffer, data from aDataBuffer. 
     Both must be ByteArray-like. The bytes in the addressBuffer must
     be a valid address for my domain (i.e. for inet, a 4-byte byteArray).
     Return the number of bytes transmitted, or a negative number on error.
     On error, the unix error code is left in the lastErrorNumber
     instance variable.
     Flags is currently ignored; it is there for ST-80 compatibility."

    ^ self sendTo:anAddressBuffer buffer:buffer start:1 for:buffer size flags:0 
!

sendTo:anAddressBuffer buffer:buffer start:startIndex for:count
    "send datagramm data - fetch address of destination host from
     anAddressBuffer, data from aDataBuffer. 
     Both must be ByteArray-like. The bytes in the addressBuffer must
     be a valid address for my domain (i.e. for inet, a 4-byte byteArray).
     Return the number of bytes transmitted, or a negative number on error.
     On error, the unix error code is left in the lastErrorNumber
     instance variable.
     Flags is currently ignored; it is there for ST-80 compatibility."

    ^ self sendTo:anAddressBuffer buffer:buffer start:startIndex for:count flags:0 
!

sendTo:anAddressBuffer buffer:aDataBuffer start:startIndex for:count flags:flags
    "send datagramm data - fetch address of destination host from
     anAddressBuffer, data from aDataBuffer starting at startIndex,
     sending count bytes. 
     Both must be ByteArray-like. The bytes in the addressBuffer must
     be a valid address for my domain (i.e. for inet, a 4-byte byteArray).
     Return the number of bytes transmitted, or a negative number on error.
     On error, the unix error code is left in the lastErrorNumber
     instance variable."

    |addrBytes addrLen nReceived portNo|

    "/ addressBuffer can be a byteArray (last 2 bytes are portNo, msb-first)
    "/ or (better) an instance of SocketAddress
    "/
    anAddressBuffer class isBytes ifTrue:[
	domain == #inet ifTrue:[
	    addrBytes := anAddressBuffer copyFrom:1 to:4.
	    portNo := ((anAddressBuffer at:5) bitShift:8)
		      + (anAddressBuffer at:6).
	] ifFalse:[
	    domain == #appletalk ifTrue:[
		addrBytes := anAddressBuffer copyFrom:1 to:3.
		portNo := ((anAddressBuffer at:5) bitShift:8)
			  + (anAddressBuffer at:6).
	    ].
	].
    ] ifFalse:[
	addrBytes := anAddressBuffer hostAddress.
	portNo := anAddressBuffer port.
    ].
%{
#ifndef NO_SOCKET
    OBJ oClass;
    OBJ fp = __INST(filePointer);
    int nInstVars, nInstBytes, objSize;
    int sock;
    union sockaddr_u sa;
    struct sockaddr *saPtr = (struct sockaddr *)&sa;
    int alen = sizeof(sa);
    int n;
    char *cp;
    int _flags = 0;
    int offs, nBytes;
    unsigned long norder;

    _flags = __longIntVal(flags);
 
    if ((fp != nil) 
     && __isSmallInteger(startIndex)
     && __isSmallInteger(count)) {
	sock = fileno(__FILEVal(fp));

	if (addrBytes == nil) {
	    alen = 0;
	    saPtr = (struct sockaddr *)0;
	} else {
	    if (! __isByteArray(addrBytes)) goto bad;

	    cp = (char *)__ByteArrayInstPtr(addrBytes)->ba_element;
	    n = __byteArraySize(addrBytes);
	    if (alen < n) n = alen;
# ifdef DGRAM_DEBUG
	    printf("address is %d bytes ... %d.%d.%d.%d", n, cp[0], cp[1], cp[2], cp[3]);
# endif
	    bcopy(cp, &sa.in.sin_addr.s_addr, n);

# ifdef AF_INET
	    if (__INST(domain) == @symbol(inet)) {
		sa.in.sin_family = AF_INET;
		sa.in.sin_port = htons((u_short) __intVal(portNo)); 
	    }
# endif
# ifdef AF_INET6
	    if (__INST(domain) == @symbol(inet6)) {
		sa.in6.sin6_family = AF_INET6;
		sa.in6.sin6_port = htons((u_short) __intVal(portNo)); 
	    }
# endif
# ifdef AF_APPLETALK
	    if (__INST(domain) == @symbol(appletalk)) {
		sa.at.sat_family = AF_APPLETALK;
		sa.at.sat_port = __intVal(portNo);
	    }
# endif
	}

	oClass = __Class(aDataBuffer);
	switch (_intVal(_ClassInstPtr(oClass)->c_flags) & ARRAYMASK) {
	    case BYTEARRAY:
		offs = __intVal(startIndex) - 1;
		break;
	    case WORDARRAY:
	    case SWORDARRAY:
		offs = (__intVal(startIndex) - 1) * 2;
		break;
	    case LONGARRAY:
	    case SLONGARRAY:
		offs = (__intVal(startIndex) - 1) * 4;
		break;
	    case LONGLONGARRAY:
	    case SLONGLONGARRAY:
		offs = (__intVal(startIndex) - 1) * 8;
# ifdef __NEED_LONGLONG_ALIGN
		offs += 4;
# endif
	    case FLOATARRAY:
		offs = (__intVal(startIndex) - 1) * sizeof(float);
		break;
	    case DOUBLEARRAY:
		offs = (__intVal(startIndex) - 1) * sizeof(double);
# ifdef __NEED_DOUBLE_ALIGN
		offs += 4;
# endif
		break;
	    default:
		goto bad;
	}
	nBytes = __intVal(count);

	nInstVars = _intVal(_ClassInstPtr(oClass)->c_ninstvars);
	nInstBytes = OHDR_SIZE + nInstVars * sizeof(OBJ);
	objSize = __qSize(aDataBuffer) - nInstBytes;
	cp = (char *)__InstPtr(aDataBuffer) + nInstBytes;
	cp += offs;
	if ((offs + nBytes) > objSize) {
# ifdef DGRAM_DEBUG
	    printf("cut off ...\n");
# endif
	    nBytes = objSize - offs;
	}

	norder = htonl(sa.in.sin_addr.s_addr);
# ifdef DGRAM_DEBUG
	printf("sending %d bytes ... to ", nBytes);
	printf("%d.%d.%d.%d\n",
		    (norder >> 24) & 0xFF,
		    (norder >> 16) & 0xFF,
		    (norder >> 8) & 0xFF,
		    norder & 0xFF);
# endif

	__BEGIN_INTERRUPTABLE__
	do {
	    n = sendto(sock, cp, nBytes, _flags, saPtr, alen);
	} while ((n < 0) && (errno == EINTR));
	__END_INTERRUPTABLE__

	if (n < 0) {
	    __INST(lastErrorNumber) = __MKSMALLINT(errno);
	}
	RETURN (__MKSMALLINT(n));
    }
#endif
bad: ;
%}.
    "
     arrive here if you try to send from an invalid buffer
     (i.e. not ByteArray-like), 
     or if the addressBuffer is nonNil AND not a ByteArray/String 
     or if the addressBuffer is nonNil AND too small.
    "
    self primitiveFailed
! !

!Socket methodsFor:'low level'!

bindAnonymously
    ^ self
	bindTo:0
	address:nil
	reuseAddress:false
!

bindAnonymouslyToAddress:addressString
    ^ self
	bindTo:0
	address:addressString
	reuseAddress:false
!

bindTo:aSocketAddress 
    "ST80 compatible bind, expecting a socketAddress argument.
     The socketAddress object (an instance of SocketAddress)
     is supposed to respond to #portOrName and #address requests."

    ^ self bindTo:(aSocketAddress portOrName)
	   address:(aSocketAddress address)
	   reuseAddress:true
!

bindTo:portNrOrNameString address:addressString
    "low level bind - returns true if ok, false otherwise.
     Currently only non-address binding is supported; 
     i.e. the address must always be nil.

     The interpretation of portNrOrName depends on the domain:
	inet domain uses (4byte) byteArray like internet numbers,
	unix domain uses pathname strings,
	others use whatever will come up in the future
     "

    ^ self 
	bindTo:portNrOrNameString 
	address:addressString 
	reuseAddress:true
!

bindTo:portNrOrName address:address reuseAddress:reuse
    "low level bind - returns true if ok, false otherwise.
     Currently only non-address binding is supported; 
     i.e. address must always be nil.

     The interpretation of portNrOrName depends on the domain:
	inet domain uses (4byte) byteArray like internet numbers,
	unix domain uses pathname strings,
	others use whatever will come up in the future

     The reuse boolean argument controls if the SO_REUSEADDR socket option
     is to be set (to avoid the 'bind: address in use' error).
    "

    filePointer isNil ifTrue:[
	^ self errorNotOpen
    ].
%{
#ifndef NO_SOCKET
    OBJ t = __INST(filePointer);
    OBJ myDomain;
    int sock;
    union sockaddr_u sa;
    int sockaddr_size;
    int ret;
    int on = 1;
    int ok;

    if (!__isString(__INST(domain)) && !__isSymbol(__INST(domain))) {
	DBGPRINTF(("SOCKET: invalid domain arg\n"));
	RETURN (false);
    }

    ok = 0;
    myDomain = __INST(domain);

# ifdef AF_INET
    if (myDomain == @symbol(inet)) {
	/*
	 * INET addresses - port must be a smallinteger or nil
	 */
	sa.in.sin_family = AF_INET;

	if (portNrOrName == nil) {
	    sa.in.sin_port = 0;
	} else {
	    if (! __isSmallInteger(portNrOrName)) {
		DBGPRINTF(("SOCKET: invalid port arg\n"));
		RETURN (false);
	    }
	    sa.in.sin_port = htons((u_short) _intVal(portNrOrName));
	}

	/*
	 * INET addresses - addr must be nil, integer or byteArray
	 */
	if (address == nil) {
	    sa.in.sin_addr.s_addr = htonl(INADDR_ANY);
	} else {
	    if (__isInteger(address)) {
		sa.in.sin_addr.s_addr = htonl(__longIntVal(address));
	    } else {
		if (__isByteArray(address)) {
		    unsigned char *cp;
		    int n;

		    cp = __ByteArrayInstPtr(address)->ba_element;
		    n = __byteArraySize(address);
		    if (n > 4) n = 4;
		    bcopy(cp, &sa.in.sin_addr.s_addr, n);
		} else {
		    unsigned addr;
		    struct hostent *hp ;

		    if (! __isString(address)) {
			DBGPRINTF(("SOCKET: invalid address arg in bind\n"));
			RETURN (false);
		    }

		    if ((addr = inet_addr(__stringVal(address))) != -1) {
			/* 
			 * is Internet addr in octet notation 
			 */
			bcopy(&addr, (char *) &sa.in.sin_addr, sizeof(addr)) ; /* set address */
		    } else {
			/* 
			 * do we know the host's address? 
			 */
			GETHOSTBYNAME(hp, __stringVal(address))
			if (hp == NULL) {
			    DBGPRINTF(("SOCKET: unknown host:%s\n", __stringVal(address)));
			    RETURN (false);
			}
			if (hp->h_addrtype != AF_INET) {
			    DBGPRINTF(("SOCKET: host:%s is not an inet host\n", __stringVal(address)));
			    RETURN (false);
			}
			bcopy(hp->h_addr, (char *) &sa.in.sin_addr, hp->h_length) ;
			sa.in.sin_family = hp->h_addrtype;
		    }
		}
	    }
	}
	DBGPRINTF(("SOCKET: bind addr: %x port: %x\n", sa.in.sin_addr.s_addr, sa.in.sin_port));
	sockaddr_size = sizeof(struct sockaddr_in);
	ok = 1;
    }
# endif /* AF_INET */

# ifdef AF_INET6
    if (myDomain == @symbol(inet6)) {
	/*
	 * INET6 addresses - port must be a smallinteger or nil
	 */
	sa.in6.sin6_family = AF_INET6;

	if (portNrOrName == nil) {
	    sa.in6.sin6_port = 0;
	} else {
	    if (! __isSmallInteger(portNrOrName)) {
		DBGPRINTF(("SOCKET: invalid port arg\n"));
		RETURN (false);
	    }
	    sa.in6.sin6_port = htons((u_short) _intVal(portNrOrName));
	}

	/*
	 * INET6 addresses - addr must be nil or byteArray or string
	 */
	if (address == nil) {
	    bzero(sa.in6.sin6_addr.s6_addr, sizeof(sa.in6.sin6_addr.s6_addr));
	} else {
	    if (__isByteArray(address)) {
		unsigned char *cp;
		int n;

		cp = __ByteArrayInstPtr(address)->ba_element;
		n = __byteArraySize(address);
		if (n > sizeof(sa.in6.sin6_addr.s6_addr)) n = sizeof(sa.in6.sin6_addr.s6_addr);
		bcopy(cp, sa.in6.sin6_addr.s6_addr, n);
	    } else {
		unsigned addr;
		struct hostent *hp ;

		if (! __isString(address)) {
		    DBGPRINTF(("SOCKET: invalid address arg in bind\n"));
		    RETURN (false);
		}

		/* 
		 * do we know the host's address? 
		 */
		GETHOSTBYNAME(hp, __stringVal(address))
		if (hp == NULL) {
		    DBGPRINTF(("SOCKET: unknown host:%s\n", __stringVal(address)));
		    RETURN (false);
		}
		if (hp->h_addrtype != AF_INET6) {
		    DBGPRINTF(("SOCKET: host:%s is not an ipv6 host\n", __stringVal(address)));
		    RETURN (false);
		}
		bcopy(hp->h_addr, (char *) &sa.in6.sin6_addr, hp->h_length) ;
		sa.in.sin_family = hp->h_addrtype;
	    }
	}

	DBGPRINTF(("SOCKET: bind addr: %x.%x.%x.%x.%x.%x... port: %x\n", 
			sa.in6.sin6_addr.s6_addr[0], 
			sa.in6.sin6_addr.s6_addr[1], 
			sa.in6.sin6_addr.s6_addr[2], 
			sa.in6.sin6_addr.s6_addr[3], 
			sa.in6.sin6_addr.s6_addr[4], 
			sa.in6.sin6_addr.s6_addr[5], 
			sa.in6.sin6_port));
	sockaddr_size = sizeof(struct sockaddr_in6);
	ok = 1;
    }
# endif /* AF_INET6 */

# ifdef AF_UNIX
    /*
     * UNIX domain - port is ignored; address must be a string (path)
     */
    if (myDomain == @symbol(unix)) {
	char *pathName;
	int l;

	if (! __isString(portNrOrName)) {
	    DBGPRINTF(("SOCKET: invalid port (pathname) arg\n"));
	    RETURN (false);
	}
	pathName = (char *)__stringVal(portNrOrName);
	l = strlen(pathName);
	if ((l + sizeof ( sa.un.sun_family )) > sizeof(struct sockaddr_un)) {
	    DBGPRINTF(("SOCKET: pathname too long\n"));
	    RETURN (false);
	}

	strcpy(sa.un.sun_path, pathName);
	sa.un.sun_family = AF_UNIX;
	sockaddr_size = l + sizeof ( sa.un.sun_family );
	ok = 1;
    }
# endif /* AF_UNIX */

# ifdef AF_APPLETALK
    /*
     * this has never been tested ....
     */
    if (myDomain == @symbol(appletalk)) {
	/*
	 * APPLETALK addresses - port must be a smallinteger or nil
	 */
	sa.at.sat_family = AF_APPLETALK;

	if (portNrOrName == nil) {
	    sa.at.sat_port = 0;
	} else {
	    if (! __isSmallInteger(portNrOrName)) {
		DBGPRINTF(("SOCKET: invalid port arg\n"));
		RETURN (false);
	    }
	    sa.at.sat_port = __intVal(portNrOrName);
	}

	/*
	 * APPLETALK addresses - addr must be nil, integer or byteArray
	 * if integer, the first byte are the hi net bits, next byte are low net bits,
	 * last byte is node.
	 */
	if (address == nil) {
	    sa.at.sat_addr.s_net = ATADDR_ANYNET;
	    sa.at.sat_addr.s_node = ATADDR_ANYNODE;
	} else {
	    if (__isInteger(address)) {
		unsigned a = __longIntVal(address);
		sa.at.sat_addr.s_net = htons((a >> 8) & 0xFFFF);
		sa.at.sat_addr.s_node = htons(a & 0xFF);
	    } else {
		if (__isByteArray(address)) {
		    unsigned char *cp;
		    int n;

		    cp = __ByteArrayInstPtr(address)->ba_element;
		    n = __byteArraySize(address);
		    if (n > 3) n = 3;
		    bcopy(cp, &sa.at.sat_addr, n);
		} else {
		    unsigned addr;
		    struct hostent *hp ;

		    if (! __isString(address)) {
			DBGPRINTF(("SOCKET: invalid address arg in bind\n"));
			RETURN (false);
		    }

		    /* 
		     * do we know the host's address? 
		     */
		    GETHOSTBYNAME(hp, __stringVal(address))
		    if (hp == NULL) {
			DBGPRINTF(("SOCKET: unknown host: %s\n", __stringVal(address)));
			RETURN (false);
		    }
		    if (hp->h_addrtype != AF_APPLETALK) {
			DBGPRINTF(("SOCKET: host:%s is not an appletalk host\n", __stringVal(address)));
			RETURN (false);
		    }
		    bcopy(hp->h_addr, (char *) &sa.at.sat_addr, hp->h_length) ;
		    sa.at.sat_family = hp->h_addrtype;
		}
	    }
	}
	DBGPRINTF(("SOCKET: bind addr: %x port: %x\n", sa.in.sin_addr.s_addr, sa.in.sin_port));
	sockaddr_size = sizeof(struct sockaddr_at);
	ok = 1;
    }
# endif /* AF_APPLETALK */

    /*
     * XXXX add addressing stuff for other domains here ...
     */
# ifdef AF_X25
    if (myDomain == @symbol(x25)) {
    }
# endif
# ifdef AF_AX25
    if (myDomain == @symbol(ax25)) {
    }
# endif
# ifdef AF_NS
    if ((myDomain == @symbol(ns)) 
     || (myDomain == @symbol(xns))) {
    }
# endif
# ifdef AF_DECnet
    if (myDomain == @symbol(decnet)) {
    }
# endif
# ifdef AF_SNA
    if (myDomain == @symbol(sna)) {
    }
# endif
# ifdef AF_RAW
    if (myDomain == @symbol(raw)) {
    }
# endif
# ifdef AF_ISO
    if (myDomain == @symbol(iso)) {
    }
# endif
# ifdef AF_NETBIOS
    if (myDomain == @symbol(netbios)) {
    }
# endif
# ifdef AF_IPX
    if (myDomain == @symbol(ipx)) {
    }
# endif
# ifdef AF_BRIDGE
    if (myDomain == @symbol(bridge)) {
    }
# endif
# ifdef AF_BSC
    if (myDomain == @symbol(bsc)) {
    }
# endif
# ifdef AF_ROSE
    if (myDomain == @symbol(rose)) {
    }
# endif
# if defined(AF_CCITT) && (AF_CCITT != AF_X25)
    if (myDomain == @symbol(ccitt)) {
    }
# endif

    if (! ok) {
	DBGPRINTF(("SOCKET: unsupported domain\n"));
	RETURN (false);
    }

    sock = fileno(__FILEVal(t));

# ifdef SO_REUSEADDR
    if (reuse == true) {
	if (setsockopt(sock, SOL_SOCKET, SO_REUSEADDR, (char *) &on, sizeof (on)) < 0) {
	    DBGPRINTF(("SOCKET: setsockopt - SO_REUSEADDR failed\n"));
	}
    }
# endif /* SO_REUSEADDR */

    __BEGIN_INTERRUPTABLE__
    do {
	ret = bind(sock, (struct sockaddr *)&sa, sockaddr_size);
    } while ((ret < 0) && (errno == EINTR));
    __END_INTERRUPTABLE__

    if (ret < 0) {
	DBGPRINTF(("SOCKET: bind failed errno=%d\n", errno));
	__INST(lastErrorNumber) = __MKSMALLINT(errno);
	RETURN (false);
    }

    __INST(port) = portNrOrName; __STORE(self, portNrOrName);

# ifdef AF_INET
    if (myDomain == @symbol(inet)) {
	if (! __isSmallInteger(portNrOrName)
	 || (portNrOrName == __MKSMALLINT(0))) {
	    int p;

	    /*
	     * INET anonymous port - get the actual portNr
	     */
	    if (getsockname(sock, (struct sockaddr *)&sa, &sockaddr_size) < 0) {
		DBGPRINTF(("SOCKET: cannot get peername\n"));
	    } else {
		DBGPRINTF(("SOCKET: anon port=%x\n", sa.in.sin_port));
		p = ntohs(sa.in.sin_port);
		__INST(port) = __MKSMALLINT(p);
	    }
	}
    }
# endif

# ifdef AF_INET6
    if (myDomain == @symbol(inet6)) {
	if (! __isSmallInteger(portNrOrName)
	 || (portNrOrName == __MKSMALLINT(0))) {
	    int p;

	    /*
	     * INET6 anonymous port - get the actual portNr
	     */
	    if (getsockname(sock, (struct sockaddr *)&sa, &sockaddr_size) < 0) {
		DBGPRINTF(("SOCKET: cannot get peername\n"));
	    } else {
		DBGPRINTF(("SOCKET: anon port=%x\n", sa.in.sin_port));
		p = ntohs(sa.in6.sin6_port);
		__INST(port) = __MKSMALLINT(p);
	    }
	}
    }
# endif

# ifdef AF_APPLETALK
    if (myDomain == @symbol(appletalk)) {
	if (! __isSmallInteger(portNrOrName)
	 || (portNrOrName == __MKSMALLINT(0))) {
	    int p;

	    /*
	     * APPLETALK anonymous port - get the actual portNr
	     */
	    if (getsockname(sock, (struct sockaddr *)&sa, &sockaddr_size) < 0) {
		DBGPRINTF(("SOCKET: cannot get peername\n"));
	    } else {
		DBGPRINTF(("SOCKET: anon port=%x\n", sa.in.sin_port));
		p = sa.at.sat_port;
		__INST(port) = __MKSMALLINT(p);
	    }
	}
    }
# endif

#else /* NO_SOCKET */
    RETURN (false);
#endif /* NO_SOCKET */
%}.
    ^ true

    "
     (Socket domain:#inet type:#stream)
	 bindTo:9999
	 address:nil
    "
!

closeFile
    "low level close"

%{  /* NOCONTEXT */
#ifndef NO_SOCKET

    OBJ t;

    t = __INST(filePointer);
    if (t != nil) {
	FILE *fp;

	fp = __FILEVal(t);
	fflush(fp);
	/* shutdown(fileno(fp), 2); */
	fclose(fp);
	__INST(filePointer) = nil;
    }
#endif
%}
!

listenFor:aNumber
    "same as listenWithBacklog: - for ST-80 compatibility"

    ^ self listenWithBacklog:aNumber
!

listenWithBacklog:aNumber
    "start listening; return true if ok, false on error"

    filePointer isNil ifTrue:[
	^ self errorNotOpen
    ].
%{
#ifndef NO_SOCKET
    OBJ fp = __INST(filePointer);
    int sock;
    int ret;

    if (! __isSmallInteger(aNumber)) {
	DBGPRINTF(("SOCKET: invalid arg\n"));
	RETURN (false);
    }

    sock = fileno(__FILEVal(fp));

    __BEGIN_INTERRUPTABLE__
    do {
	ret = listen(sock, _intVal(aNumber));
    } while ((ret < 0) && (errno == EINTR));
    __END_INTERRUPTABLE__

    if (ret < 0) {
	DBGPRINTF(("SOCKET: listen call failed errno=%d\n", errno));
	__INST(lastErrorNumber) = __MKSMALLINT(errno);
	RETURN (false);
    }
#else
    RETURN (false);
#endif
%}.
    ^ true
!

shutDown 
    "shutDown without flushing "

    filePointer isNil ifTrue:[^ self].
    Lobby unregister:self.

%{
#ifndef NO_SOCKET

    OBJ fp;

    fp = __INST(filePointer);
    if (fp != nil) {
	FILE *f;
	int fd;

	__INST(filePointer) = nil;
	f = __FILEVal(fp);
	fd = fileno(f);
	__BEGIN_INTERRUPTABLE__
	shutdown(fd, 2);
	fclose(f);
	/* close(fd); */
	__END_INTERRUPTABLE__
    }
#endif
%}
! !

!Socket methodsFor:'low level-accepting'!

accept
    "create a new TCP socket from accepting on the receiver.
     This method will suspend the current process if no connection is waiting.
     For ST-80 compatibility"

    |newSock|

    newSock := self class new.
    (newSock acceptOn:self) ifFalse:[^ nil].
    ^ newSock

    "
     |sock newSock|

     sock := Socket provide:8004.
     sock listenFor:5.
     newSock := sock accept.
    "
!

acceptOn:aSocket
    "accept a connection on a server port (created with:'Socket>>onIPPort:')
     usage is: (Socket basicNew acceptOn:(Socket onIPPort:9999)).
     This method will suspend the current process if no connection is waiting.
     Return the true if ok; false if not."

    aSocket readWriteWait.
    ^ self blockingAcceptOn:aSocket

    "Modified: / 11.3.1996 / 14:21:31 / stefan"
    "Modified: / 1.8.1998 / 23:39:10 / cg"
!

blockingAcceptOn:aSocket
    "accept a connection on a server port (created with:'Socket>>onIPPort:')
     usage is: (Socket basicNew acceptOn:(Socket onIPPort:9999)).
     Return the true if ok; false if not.

     NOTICE: this method will block, if no connection is already pending.
             use readWait or Socket>>accept."

    |serverSocketFd|

    filePointer notNil ifTrue:[
        ^ self errorAlreadyOpen
    ].

    domain := aSocket domain.
    socketType := aSocket type.
    serverSocketFd := aSocket fileDescriptor.
    serverSocketFd isNil ifTrue:[
        ^ self error:'invalid server socket'
    ].
    (serverSocketFd isMemberOf:SmallInteger) ifFalse:[
        ^ self error:'invalid server socket'
    ].
%{
#ifndef NO_SOCKET
    FILE *fp;
    int flags;
    int sock, newSock;
    union sockaddr_u sa;
    int alen, alen0;
    struct hostent *he ;
    char dotted[20] ;

    sock = _intVal(serverSocketFd);

#if defined(O_NDELAY) && defined(SET_NDELAY)
    flags = ioctl(sock, F_GETFL, 0);
    ioctl(sock, F_SETFL, flags | O_NDELAY);
#endif

#ifdef AF_INET
    if (__INST(domain) == @symbol(inet)) {
        alen0 = sizeof(sa.in);
    }
#endif
#ifdef AF_INET6
    if (__INST(domain) == @symbol(inet6)) {
        alen0 = sizeof(sa.in6);
    }
#endif
#ifdef AF_UNIX
    if (__INST(domain) == @symbol(unix)) {
        alen0 = sizeof(sa.un);
    }
#endif
# ifdef AF_APPLETALK
    if (__INST(domain) == @symbol(appletalk)) {
        alen0 = sizeof(sa.at);
    }
# endif

    /*
     * XXXX add addressing stuff for other domains here ...
     */
# ifdef AF_X25
    if (__INST(domain) == @symbol(x25)) {
        alen0 = sizeof(sa.x25);
    }
# endif
# ifdef AF_AX25
    if (__INST(domain) == @symbol(ax25)) {
        alen0 = sizeof(sa.ax25);
    }
# endif
# ifdef AF_NS
    if ((__INST(domain) == @symbol(ns)) 
     || (__INST(domain) == @symbol(xns))) {
    }
# endif
# ifdef AF_DECnet
    if (__INST(domain) == @symbol(decnet)) {
        alen0 = sizeof(sa.dn);
    }
# endif
# ifdef AF_SNA
    if (__INST(domain) == @symbol(sna)) {
        alen0 = sizeof(sa.sna);
    }
# endif
# ifdef AF_RAW
    if (__INST(domain) == @symbol(raw)) {
    }
# endif
# ifdef AF_ISO
    if (__INST(domain) == @symbol(iso)) {
    }
# endif
# ifdef AF_NETBIOS
    if (__INST(domain) == @symbol(netbios)) {
    }
# endif
# ifdef AF_IPX
    if (__INST(domain) == @symbol(ipx)) {
        alen0 = sizeof(sa.ipx);
    }
# endif
# ifdef AF_BRIDGE
    if (__INST(domain) == @symbol(bridge)) {
    }
# endif
# ifdef AF_BSC
    if (__INST(domain) == @symbol(bsc)) {
    }
# endif
# ifdef AF_ROSE
    if (__INST(domain) == @symbol(rose)) {
    }
# endif
# if defined(AF_CCITT) && (AF_CCITT != AF_X25)
    if (__INST(domain) == @symbol(ccitt)) {
    }
# endif

    __BEGIN_INTERRUPTABLE__
    do {
        alen = alen0;
        newSock = accept(sock, (struct sockaddr *) &sa, &alen);
    } while ((newSock < 0) && (errno == EINTR));
    __END_INTERRUPTABLE__

#if defined(O_NDELAY) && defined(SET_NDELAY)
    ioctl(sock, F_SETFL, flags);
#endif

    if (newSock < 0) {
        DBGPRINTF(("SOCKET: accept call failed errno=%d\n", errno));
        __INST(lastErrorNumber) = __MKSMALLINT(errno);
        RETURN (false);
    }

    /*
     * extract the partners address
     */
#ifdef AF_INET
    if (__INST(domain) == @symbol(inet)) {
        GETHOSTBYADDR(he, (char *) &sa.in.sin_addr, sizeof(sa.in.sin_addr), AF_INET);
        if (! he) {
            unsigned long norder;

            norder = htonl(sa.in.sin_addr.s_addr) ;
            sprintf(dotted, "%d.%d.%d.%d",
                    (norder >> 24) & 0xFF,
                    (norder >> 16) & 0xFF,
                    (norder >> 8) & 0xFF,
                    norder & 0xFF);
        }
        DBGPRINTF(("SOCKET: accepted connection from host %s\n", (he ? he->h_name : dotted))) ;
        __INST(peerName) = __MKSTRING((he ? he->h_name : dotted));
        __STORESELF(peerName);
    }
#endif

#ifdef AF_INET6
    if (__INST(domain) == @symbol(inet6)) {
        GETHOSTBYADDR(he, (char *) &sa.in6.sin6_addr, sizeof(sa.in.sin6_addr), AF_INET6);
        if (! he) {
            unsigned long norder;

            /*
             * XXX: what is inet6's naming convention ?
             */
            norder = htonl(sa.in.sin_addr.s_addr) ;
            sprintf(dotted, "%d.%d.%d.%d.%d.%d...",
                    sa.in6.sin6_addr.s6_addr[0],
                    sa.in6.sin6_addr.s6_addr[1],
                    sa.in6.sin6_addr.s6_addr[2],
                    sa.in6.sin6_addr.s6_addr[3],
                    sa.in6.sin6_addr.s6_addr[4],
                    sa.in6.sin6_addr.s6_addr[5]);
        }
        DBGPRINTF(("SOCKET: accepted connection from host %s\n", (he ? he->h_name : dotted))) ;
        __INST(peerName) = __MKSTRING((he ? he->h_name : dotted));
        __STORESELF(peerName);
    }
#endif

#ifdef AF_UNIX
    if (__INST(domain) == @symbol(unix)) {
        DBGPRINTF(("SOCKET: accepted connection on unix socket\n")) ;
        /* nothing to be done here */
    }
#endif

#ifdef AF_APPLETALK
    if (__INST(domain) == @symbol(appletalk)) {
        GETHOSTBYADDR(he, (char *) &sa.at.sat_addr, sizeof(sa.in.sat_addr), AF_APPLETALK);
        if (! he) {
            unsigned net;

            /*
             * XXX: what is apples naming convention ?
             */
            net = htons(sa.at.sat_addr.s_net) ;
            sprintf(dotted, "%d.%d",
                    net,
                    sa.at.sat_addr.s_node);
        }
        DBGPRINTF(("SOCKET: accepted connection from host %s\n", (he ? he->h_name : dotted))) ;
        __INST(peerName) = __MKSTRING((he ? he->h_name : dotted));
        __STORESELF(peerName);
    }
# endif

    /*
     * XXXX add addressing stuff for other domains here ...
     */
# ifdef AF_X25
    if (__INST(domain) == @symbol(x25)) {
    }
# endif
# ifdef AF_AX25
    if (__INST(domain) == @symbol(ax25)) {
    }
# endif
# ifdef AF_NS
    if ((__INST(domain) == @symbol(ns)) 
     || (__INST(domain) == @symbol(xns))) {
    }
# endif
# ifdef AF_DECnet
    if (__INST(domain) == @symbol(decnet)) {
    }
# endif
# ifdef AF_SNA
    if (__INST(domain) == @symbol(sna)) {
    }
# endif
# ifdef AF_RAW
    if (__INST(domain) == @symbol(raw)) {
    }
# endif
# ifdef AF_ISO
    if (__INST(domain) == @symbol(iso)) {
    }
# endif
# ifdef AF_NETBIOS
    if (__INST(domain) == @symbol(netbios)) {
    }
# endif
# ifdef AF_IPX
    if (__INST(domain) == @symbol(ipx)) {
    }
# endif
# ifdef AF_BRIDGE
    if (__INST(domain) == @symbol(bridge)) {
    }
# endif
# ifdef AF_BSC
    if (__INST(domain) == @symbol(bsc)) {
    }
# endif
# ifdef AF_ROSE
    if (__INST(domain) == @symbol(rose)) {
    }
# endif
# if defined(AF_CCITT) && (AF_CCITT != AF_X25)
    if (__INST(domain) == @symbol(ccitt)) {
    }
# endif

    /* 
     * make it a FILE * 
     */
    fp = fdopen(newSock, "r+");
    if (! fp) {
        DBGPRINTF(("SOCKET: fdopen call failed\n"));
        __INST(lastErrorNumber) = __MKSMALLINT(errno);
        close(newSock);
        RETURN (false);
    } else {
#ifdef BUGGY_STDIO_LIB
        setbuf(fp, NULL);
        __INST(buffered) = false;
#endif
        __INST(filePointer) = __MKOBJ(fp);
        __STORESELF(filePointer);
    }
#endif
%}.
    mode := #readwrite.
    Lobby register:self.
    binary := false.
    port := aSocket port.
    ^ true
!

waitForNewConnectionOrDataOnAny:otherConnections timeout:timeoutSeconds
    "suspend the current process, until either a new connection comes
     in at the receiver, or data arrives on any of the otherConnections.
     For a new connection, an accept is performed and the new socket is returned.
     For an old connection, that socket is returned.
     In any case, the caller gets a socket to operate on as return value,
     or nil, if a timeout occured.
     This method implements the inner wait-primitive of a multi-connection 
     server application."

    "/ first, a quick check if data is already available

    |connection wasBlocked sema|

    self canReadWithoutBlocking ifTrue:[
	^ self accept.
    ].
    otherConnections do:[:aConnection |
	aConnection canReadWithoutBlocking ifTrue:[
	    ^ aConnection
	]
    ].

    [
	"/ check again - prevent incoming interrupts from disturbing our setup
	wasBlocked := OperatingSystem blockInterrupts.

	self canReadWithoutBlocking ifTrue:[
	    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
	    ^ self accept.
	].
	otherConnections do:[:aConnection |
	    aConnection canReadWithoutBlocking ifTrue:[
		wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
		^ aConnection
	    ]
	].

	"/ nope - must wait.

	sema := Semaphore new name:'multiReadWait'.
	otherConnections do:[:aConnection |
	    Processor signal:sema onInput:(aConnection fileDescriptor).
	].
	Processor signal:sema onInput:(self fileDescriptor).
	timeoutSeconds notNil ifTrue:[
	    Processor signal:sema afterSeconds:timeoutSeconds 
	].
	Processor activeProcess state:#ioWait.
	sema wait.
	Processor disableSemaphore:sema.

    ] valueOnUnwindDo:[
	Processor disableSemaphore:sema.
	wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
    ].

    "/ see who it was ...

    self canReadWithoutBlocking ifTrue:[
	^ self accept.
    ].
    otherConnections do:[:aConnection |
	aConnection canReadWithoutBlocking ifTrue:[
	    ^ aConnection
	]
    ].

    "/ none - a timeout
    ^ nil
! !

!Socket methodsFor:'low level-connecting'!

connectTo:hostOrPathName port:portNrOrName
    "low level connect; connect to port, portNrOrName on host, hostName.
     For unix-domain sockets, the port argument is ignored and pathName is taken.
     Other sockets are not yet implemented.
     Return true if ok, false otherwise.
     Hostname must be a string, portNrOrName an integer port number (in inet domain).
     The current process will block (but not the whole Smalltalk) until the connection
     is established. 
     See also: #connectTo:port:withTimeout: for a somewhat nicer interface."

    ^ self connectTo:hostOrPathName port:portNrOrName blocking:false
!

connectTo:hostOrPathName port:portNrOrName blocking:blocking
    "low level connect; connect to port, portNrOrName on host, hostName.
     For unix-domain sockets, the port argument is ignored and pathName is taken.
     Other sockets are not yet implemented.
     Return true if ok, false otherwise.
     Hostname must be a string, portNrOrName an integer port number (in inet domain).
     The current process will block (but not the whole Smalltalk) until the connection
     is established. 
     See also: #connectTo:port:withTimeout: for a somewhat nicer interface."

    |isAsync|

    filePointer isNil ifTrue:[
	^ self errorNotOpen
    ].
%{

#ifndef NO_SOCKET
    OBJ t = __INST(filePointer);
    OBJ myDomain;
    union sockaddr_u sa;
    struct hostent *hp ;
    int a, sock ;
    long addr;
    FILE *fp;
    int ret, oldFlags;
    int on = 1;
    int ok;
    int sockaddr_size;

    if (!__isString(__INST(domain)) && !__isSymbol(__INST(domain))) {
	DBGPRINTF(("SOCKET: invalid domain arg\n"));
	RETURN (false);
    }

    ok = 0;
    myDomain = __INST(domain);
    bzero((char *) &sa, sizeof(sa)) ;

#ifdef AF_INET
    if (myDomain == @symbol(inet)) {
	/*
	 * INET addressing: port must be a smallInteger;
	 * hostOrPathName the name of the host (dot notation allowed)
	 * or a byteArray containing the 4 address bytes.
	 */
	if (! __isSmallInteger(portNrOrName)) {
	    DBGPRINTF(("SOCKET: invalid port arg\n"));
	    RETURN (false);
	}

	sa.in.sin_family = AF_INET;
	sa.in.sin_port = htons((u_short) _intVal(portNrOrName)) ;

	if (__isByteArray(hostOrPathName)) {
	    unsigned char *cp;
	    int n;

	    cp = __ByteArrayInstPtr(hostOrPathName)->ba_element;
	    n = __byteArraySize(hostOrPathName);
	    if (n > 4) n = 4;
	    bcopy(cp, &sa.in.sin_addr.s_addr, n);
	} else {
	    if (! __isString(hostOrPathName)) {
		DBGPRINTF(("SOCKET: invalid hostname arg\n"));
		RETURN (false);
	    }

	    if ((addr = inet_addr(__stringVal(hostOrPathName))) != -1) {
		/* 
		 * is Internet addr in octet notation 
		 */
		bcopy(&addr, (char *) &sa.in.sin_addr, sizeof(addr)) ; /* set address */
	    } else {
		/* 
		 * do we know the host's address? 
		 */
		GETHOSTBYNAME(hp, __stringVal(hostOrPathName))
		if (hp == NULL) {
		    DBGPRINTF(("SOCKET: unknown host:%s\n", __stringVal(hostOrPathName)));
		    RETURN (false);
		}
		bcopy(hp->h_addr, (char *) &sa.in.sin_addr, hp->h_length) ;
		sa.in.sin_family = hp->h_addrtype;
	    }
	}

	DBGPRINTF(("SOCKET: connect addr: %x port: %d\n", sa.in.sin_addr, sa.in.sin_port));

	sockaddr_size = sizeof(struct sockaddr_in);
	ok = 1;
    }
#endif /* AF_INET */

#ifdef AF_INET6
    if (myDomain == @symbol(inet6)) {
	/*
	 * INET6 addressing: port must be a smallInteger;
	 * hostOrPathName the name of the host
	 * or a byteArray containing the address bytes.
	 */
	if (! __isSmallInteger(portNrOrName)) {
	    DBGPRINTF(("SOCKET: invalid port arg\n"));
	    RETURN (false);
	}

	sa.in6.sin6_family = AF_INET6;
	sa.in6.sin6_port = htons((u_short) _intVal(portNrOrName)) ;

	if (__isByteArray(hostOrPathName)) {
	    unsigned char *cp;
	    int n;

	    cp = __ByteArrayInstPtr(hostOrPathName)->ba_element;
	    n = __byteArraySize(hostOrPathName);
	    if (n > sizeof(sa.in6.sin6_addr.s6_addr)) n = sizeof(sa.in6.sin6_addr.s6_addr);
	    bcopy(cp, sa.in6.sin6_addr.s6_addr, n);
	} else {
	    if (! __isString(hostOrPathName)) {
		DBGPRINTF(("SOCKET: invalid hostname arg\n"));
		RETURN (false);
	    }

	    /* 
	     * do we know the host's address? 
	     */
	    GETHOSTBYNAME(hp, __stringVal(hostOrPathName))
	    if (hp == NULL) {
		DBGPRINTF(("SOCKET: unknown host:%s\n", __stringVal(hostOrPathName)));
		RETURN (false);
	    }
	    bcopy(hp->h_addr, (char *) &sa.in.sin_addr, hp->h_length) ;
	    sa.in.sin_family = hp->h_addrtype;
	}

	DBGPRINTF(("SOCKET: connect addr: %x.%x.%x.%x.%x.%x... port: %d\n", 
		sa.in6.sin6_addr.s6_addr[0],
		sa.in6.sin6_addr.s6_addr[1],
		sa.in6.sin6_addr.s6_addr[2],
		sa.in6.sin6_addr.s6_addr[3],
		sa.in6.sin6_addr.s6_addr[4],
		sa.in6.sin6_addr.s6_addr[5],
		sa.in6.sin6_port));

	sockaddr_size = sizeof(struct sockaddr_in6);
	ok = 1;
    }
#endif /* AF_INET6 */

#ifdef AF_UNIX
    if (myDomain == @symbol(unix)) {
	char *pathName;
	int l;

	/*
	 * UNIX domain: port is ignored;
	 * hostOrPathName is a pathName
	 */
	if (! __isString(hostOrPathName)) {
	    DBGPRINTF(("SOCKET: invalid port (pathname) arg\n"));
	    RETURN (false);
	}
	pathName = (char *) __stringVal(hostOrPathName);
	l = strlen(pathName);
	if ((l + sizeof ( sa.un.sun_family )) > sizeof(struct sockaddr_un)) {
	    DBGPRINTF(("SOCKET: pathname too long\n"));
	    RETURN (false);
	}

	strcpy(sa.un.sun_path, pathName);
	sa.un.sun_family = AF_UNIX;
	sockaddr_size = l + sizeof ( sa.un.sun_family );
	ok = 1;
    }
#endif /* AF_UNIX */

#ifdef AF_APPLETALK
    if (myDomain == @symbol(appletalk)) {
	/*
	 * APPLETALK addressing: port must be a smallInteger;
	 * hostOrPathName the name of the host
	 * or a byteArray containing the 3 address bytes.
	 */
	if (! __isSmallInteger(portNrOrName)) {
	    DBGPRINTF(("SOCKET: invalid port arg\n"));
	    RETURN (false);
	}

	sa.at.sat_family = AF_APPLETALK;
	sa.at.sat_port = __intVal(portNrOrName);

	if (__isByteArray(hostOrPathName)) {
	    unsigned char *cp;
	    int n;

	    cp = __ByteArrayInstPtr(hostOrPathName)->ba_element;
	    n = __byteArraySize(hostOrPathName);
	    if (n > 3) n = 3;
	    bcopy(cp, &sa.at.sat_addr, n);
	} else {
	    if (! __isString(hostOrPathName)) {
		DBGPRINTF(("SOCKET: invalid hostname arg\n"));
		RETURN (false);
	    }

	    /* 
	     * do we know the host's address? 
	     */
	    GETHOSTBYNAME(hp, __stringVal(hostOrPathName))
	    if (hp == NULL) {
		DBGPRINTF(("SOCKET: unknown host:%s\n", __stringVal(hostOrPathName)));
		RETURN (false);
	    }
	    if (hp->h_addrtype != AF_APPLETALK) {
		DBGPRINTF(("SOCKET: host:%s is not an appletalk host\n", __stringVal(hostOrPathName)));
		RETURN (false);
	    }

	    bcopy(hp->h_addr, (char *) &sa.at.sat_addr, hp->h_length) ;
	    sa.at.sat_family = hp->h_addrtype;
	}

	DBGPRINTF(("SOCKET: connect addr: %x port: %d\n", sa.in.sin_addr, sa.in.sin_port));

	sockaddr_size = sizeof(struct sockaddr_at);
	ok = 1;
    }
#endif /* APPLETALK */

    /*
     * XXXX add addressing stuff for other domains here ...
     */
#ifdef AF_X25
    if (myDomain == @symbol(x25)) {
    }
#endif
#ifdef AF_AX25
    if (myDomain == @symbol(ax25)) {
    }
#endif
#ifdef AF_NS
    if ((myDomain == @symbol(ns)) 
     || (myDomain == @symbol(xns))) {
    }
#endif
# ifdef AF_DECnet
    if (myDomain == @symbol(decnet)) {
    }
# endif
#ifdef AF_SNA
    if (myDomain == @symbol(sna)) {
    }
#endif
#ifdef AF_RAW 
    if (myDomain == @symbol(raw)) {
    }
#endif
# ifdef AF_ISO
    if (myDomain == @symbol(iso)) {
    }
# endif
# ifdef AF_NETBIOS
    if (myDomain == @symbol(netbios)) {
    }
# endif
# ifdef AF_IPX
    if (myDomain == @symbol(ipx)) {
    }
# endif
# ifdef AF_BRIDGE
    if (myDomain == @symbol(bridge)) {
    }
# endif
# ifdef AF_BSC
    if (myDomain == @symbol(bsc)) {
    }
# endif
# ifdef AF_ROSE
    if (myDomain == @symbol(rose)) {
    }
# endif
# if defined(AF_CCITT) && (AF_CCITT != AF_X25)
    if (myDomain == @symbol(ccitt)) {
    }
# endif

    if (! ok) {
	DBGPRINTF(("SOCKET: unsupported domain\n"));
	RETURN (false);
    }

    sock = fileno(__FILEVal(t));

#if defined(O_NONBLOCK)
    if (blocking != true) {
	/*
	 * set to non-blocking and wait later
	 */
	oldFlags = fcntl(sock, F_GETFL, 0);
	/* on SUNOS4.x, would use fcntl(osfd, F_SETFL, flags | FNDELAY); */
	fcntl(sock, F_SETFL, oldFlags | O_NONBLOCK);
    }
#endif

    /* 
     * connect 
     */
    __BEGIN_INTERRUPTABLE__
    do {
	ret = connect(sock, (struct sockaddr *)&sa, sockaddr_size);
    } while ((ret < 0) 
	     && ((errno == EINTR)
#ifdef EAGAIN
		 || (errno == EAGAIN)
#endif
		));
    __END_INTERRUPTABLE__

    if (ret < 0) { 
#if defined(EINPROGRESS) || defined(EALREADY)
	if (0
# ifdef EINPROGRESS
	    || (errno == EINPROGRESS) 
# endif
# ifdef EALREADY
	    || (errno == EALREADY)
# endif
	) {
	    /*
	     * We were interrupted. Do not call connect again
	     * (we will get an EALREADY.
	     * Do a select on write instead.
	     */

	    isAsync = true;
	} else
#endif /* EINPROGRESS or EALREADY */
	{
	    DBGPRINTF(("SOCKET: connect failed errno=%d\n", errno));
#ifdef DUMP_ADDRESS
	    {
		char *cp = (char *)(&sa);
		int i;

		printf("address data:\n");
		for (i=0; i<sockaddr_size; i++) {
		    printf(" %02x\n", *cp++);
		}
	    }
#endif
	    __INST(lastErrorNumber) = __MKSMALLINT(errno);
	    RETURN (false);
	}
    }

#if defined(O_NONBLOCK)
    if (blocking != true) {
	fcntl(sock, F_SETFL, oldFlags);
    }
#endif

#else /* NO_SOCKET */
    RETURN (false);
#endif /* NO_SOCKET */
%}.
    isAsync == true ifTrue:[
	self readWriteWait.
    ].
    port := portNrOrName.
    peerName := hostOrPathName.
    ^ true
!

connectTo:hostOrPathName port:portNrOrName blocking:blocking withTimeout:millis
    "connect to port, portNrOrName on host, hostName.
     Or path (UNIX socket), where portNrOrName is ignored.
     Return true if ok, false otherwise.
     Hostname must be a string, portNrOrName an integer port number (in inet domain).
     If a non-nil timeout is given, stop trying after that time and return false as well."

    |stopSignal stopMe connection|

    millis isNil ifTrue:[
	^ self connectTo:hostOrPathName port:portNrOrName
    ].

    stopSignal := Signal new.
    stopMe := [stopSignal raise].
    stopSignal handle:[:ex |
"/        'timeout on connect' infoPrintNL.
	^ false
    ] do:[
	Processor addTimedBlock:stopMe afterMilliseconds:millis.
	[
	    connection := self connectTo:hostOrPathName port:portNrOrName blocking:blocking.
	] valueNowOrOnUnwindDo:[
	    Processor removeTimedBlock:stopMe.
	]
    ].
    ^ connection

    "Created: 31.10.1995 / 18:52:49 / cg"
    "Modified: 16.8.1997 / 02:11:21 / cg"
!

connectTo:hostOrPathName port:portNrOrName withTimeout:millis
    "connect to port, portNrOrName on host, hostName.
     Or path (UNIX socket), where portNrOrName is ignored.
     Return true if ok, false otherwise.
     Hostname must be a string, portNrOrName an integer port number (in inet domain).
     If a non-nil timeout is given, stop trying after that time and return false as well."

    ^ self connectTo:hostOrPathName port:portNrOrName blocking:false withTimeout:millis
! !

!Socket methodsFor:'queries'!

domain
    "return the sockets addressing domain (i.e. #inet, #unix, #x25, #appletalk)"

    ^ domain
!

getName
    "return the name; here, we return the ports name"

    ^ port printString
!

getPeer
    "ST-80 compatibility: return an IPSocketAddress instance representing
     my hostname/port combination.
     If you are interested in the hostname, use getPeerName directly."

    domain == #unix ifTrue:[
	^ UDSocketAddress name:peerName
    ].
    domain == #inet ifTrue:[
	^ IPSocketAddress hostAddress:(self class ipAddressOfHost:peerName) port:port
    ].
    domain == #inet6 ifTrue:[
	^ IPv6SocketAddress hostAddress:(self class ipV6AddressOfHost:peerName) port:port
    ].
    domain == #appletalk ifTrue:[
	^ AppletalkSocketAddress hostAddress:(self class appletalkAddressOfHost:peerName) port:port
    ].
    domain == #decnet ifTrue:[
	^ DecNetSocketAddress hostAddress:(self class decnetAddressOfHost:peerName) port:port
    ].
    self error:'unsupported domain'.

    "Created: 2.11.1995 / 11:22:39 / cg"
!

getPeerName
    "return the peer name; thats the hostname (or dotted name) of the
     partners host after an accept."

    ^ peerName
!

isActive
    "return true, if the receiver has a connection"

    ^ filePointer notNil
!

port
    "return the port number (or name for unix-sockets) to which the socket is bound"

    |p|

    port == 0 ifTrue:[
	p := self getPort.
	p notNil ifTrue:[
	    port := p
	]
    ].
    ^ port
!

type
    "return the sockets connection type (i.e. #datagram, #stream etc)"

    ^ socketType
! !

!Socket methodsFor:'socket setup'!

domain:domainArg type:typeArg
    "set up socket with domain and type.
     This is a low level entry; no binding, listening or connect
     is done. Both arguments must be symbols from one of
     #inet,#unix, #appletalk, #x25 .. and #stream, #datagram, #raw resp."

    ^ self domain:domainArg type:typeArg protocol:0 reuseAddress:true
!

domain:domainArg type:typeArg protocol:protocolNumber
    "set up socket with domain, type and protocol number.
     This is a low level entry; no binding, listening or connect
     is done. Both arguments must be symbols from one of
     #inet,#unix, #appletalk, #x25 .. and #stream, #datagram, #raw resp."

    ^ self domain:domainArg type:typeArg protocol:protocolNumber reuseAddress:true

    "
     Socket new domain:#inet type:#stream
     Socket new domain:#unix type:#stream
    "
!

domain:domainArg type:typeArg protocol:protocolNumber reuseAddress:reuse
    "set up socket with domain, type and protocol number.
     This is a low level entry; no binding, listening or connect
     is done. Both arguments must be symbols from one of
     #inet,#unix, #appletalk, #x25 .. and #stream, #datagram, #raw resp.

     The reuse boolean argument controls if the SO_REUSEADDR socket option
     is to be set (to avoid the 'bind: address in use' error)."

    |errorNr|

    filePointer notNil ifTrue:[
	^ self errorAlreadyOpen
    ].
%{

#ifndef NO_SOCKET
    FILE *fp;
    int dom, typ, pf, proto = 0, sock;
    int on = 1;

    if (! __isSymbol(domainArg)) { 
	DBGPRINTF(("SOCKET: bad domain\n"));
	RETURN ( nil );
    }
    if (! __isSymbol(typeArg)) { 
	DBGPRINTF(("SOCKET: bad type\n"));
	RETURN ( nil );
    }
    if (protocolNumber != nil) {
	if (!__isSmallInteger(protocolNumber)) {
	    DBGPRINTF(("SOCKET: bad protocol\n"));
	    RETURN ( nil );
	}
	proto = __intVal(protocolNumber);
    }
        

    /*
     * get address and protocol-family
     */
#ifdef AF_UNIX
    if (domainArg == @symbol(unix)) {
	dom = AF_UNIX;
    } else
#endif
#ifdef AF_INET
    if (domainArg == @symbol(inet)) {
	dom = AF_INET;
    } else
#endif
#ifdef AF_INET6
    if (domainArg == @symbol(inet6)) {
	dom = AF_INET6;
    } else
#endif
#ifdef AF_DECnet
    if (domainArg == @symbol(decnet)) {
	dom = AF_DECnet;
    } else
#endif
#ifdef AF_APPLETALK
    if (domainArg == @symbol(appletalk)) {
	dom = AF_APPLETALK;
    } else
#endif
#ifdef AF_X25
    if (domainArg == @symbol(x25)) {
	dom = AF_X25;
    } else
#endif
#ifdef AF_AX25
    if (domainArg == @symbol(ax25)) {
	dom = AF_AX25;
    } else
#endif
#ifdef AF_NS
    if ((domainArg == @symbol(xns))
     || (domainArg == @symbol(ns))) {
	dom = AF_NS;
    } else
#endif
#ifdef AF_SNA
    if (domainArg == @symbol(sna)) {
	dom = AF_SNA;
    } else
#endif
#ifdef AF_RAW
    if (domainArg == @symbol(raw)) {
	dom = AF_RAW;
    } else
#endif
# ifdef AF_ISO
    if (domainArg == @symbol(iso)) {
	dom = AF_ISO;
    }
# endif
# ifdef AF_NETBIOS
    if (domainArg == @symbol(netbios)) {
	dom = AF_NETBIOS;
    }
# endif
# ifdef AF_IPX
    if (domainArg == @symbol(ipx)) {
	dom = AF_IPX;
    }
# endif
# ifdef AF_BRIDGE
    if (domainArg == @symbol(bridge)) {
	dom = AF_BRIDGE;
    }
# endif
# ifdef AF_BSC
    if (domainArg == @symbol(bsc)) {
	dom = AF_BSC;
    }
# endif
# ifdef AF_ROSE
    if (domainArg == @symbol(rose)) {
	dom = AF_ROSE;
    }
# endif
# if defined(AF_CCITT) && (AF_CCITT != AF_X25)
    if (domainArg == @symbol(ccitt)) {
	dom = AF_CCITT;
    }
# endif
    {
	DBGPRINTF(("SOCKET: unknown domain <%s>\n", __stringVal(domainArg)));
	RETURN ( nil );
    }

#ifdef SOCK_STREAM
    if (typeArg == @symbol(stream)) {
	typ = SOCK_STREAM;
    } else
#endif
#ifdef SOCK_DGRAM
    if (typeArg == @symbol(datagram)) {
	typ = SOCK_DGRAM;
    } else 
#endif
#ifdef SOCK_RAW
    if (typeArg == @symbol(raw))
	typ = SOCK_RAW;
    else
#endif
#ifdef SOCK_SEQPACKET
    if (typeArg == @symbol(seqPacket))
	typ = SOCK_SEQPACKET;
    else
#endif
    {
	DBGPRINTF(("SOCKET: bad type <%s>\n", __stringVal(typeArg)));
	RETURN ( nil );
    }

    __BEGIN_INTERRUPTABLE__
    do {
	DBGPRINTF(("SOCKET: opening socket domain=%d type=%d proto=%d\n", dom, typ, proto));
	sock = socket(dom, typ, proto);
#if defined(EPROTONOSUPPORT) /* for SGI */
	if ((proto != 0) && (sock < 0) && (errno == EPROTONOSUPPORT)) {
	    DBGPRINTF(("SOCKET: retry with UNSPEC protocol\n"));
	    proto = 0;
	    sock = socket(dom, typ, 0);
	}
#endif
    } while ((sock < 0) && (errno == EINTR));
    __END_INTERRUPTABLE__

    if (sock < 0) {
	DBGPRINTF(("SOCKET: socket(dom=%d typ=%d proto=%d) call failed errno=%d\n", dom, typ, proto, errno));
	__INST(lastErrorNumber) = __MKSMALLINT(errno);
    } else {
# ifdef SO_REUSEADDR
	if (reuse == true) {
	    DBGPRINTF(("SOCKET: setsockopt - SO_REUSEADDR\n"));
	    if (setsockopt(sock, SOL_SOCKET, SO_REUSEADDR, (char *) &on, sizeof (on)) < 0) {
		DBGPRINTF(("SOCKET: setsockopt - SO_REUSEADDR failed\n"));
	    }
	}
# endif /* SO_REUSEADDR */

	/* 
	 * make it a FILE * 
	 */
	fp = fdopen(sock, "r+");
	if (! fp) {
	    DBGPRINTF(("SOCKET: fdopen call failed\n"));
	    __INST(lastErrorNumber) = __MKSMALLINT(errno);
	    __BEGIN_INTERRUPTABLE__
	    close(sock);
	    __END_INTERRUPTABLE__
	} else {
	    __INST(filePointer) = __MKOBJ(fp);
	    __STORESELF(filePointer);
	}
    }
#endif
%}.

    "all ok?"
    filePointer notNil ifTrue:[
	domain := domainArg.
	socketType := typeArg.
	Lobby register:self.
    ] ifFalse:[
	^ nil
    ].

    "
     Socket new domain:#inet type:#stream
     Socket new domain:#unix type:#stream
    "
!

for:hostName port:portNr
    "setup for a TCP socket (i.e. inet domain, stream type) 
     If hostname is nil, a server port is opened,
     otherwise a client port to the server on host.

     HISTORIC LEFTOVER:
     This method will vanish, as soon as the low level
     connect/bind works,"

    self obsoleteMethodWarning.

    filePointer notNil ifTrue:[
	^ self errorAlreadyOpen
    ].
    (portNr isMemberOf:SmallInteger) ifFalse:[
	self error:'invalid portNr'
    ].
%{
#ifndef NO_SOCKET
    struct sockaddr_in sa ;
    struct hostent *hp ;
    int a, sock ;
    long addr;
    FILE *fp;
    int ret;
    int on = 1;

    bzero((char *) &sa, sizeof(sa)) ;
    sa.sin_family = AF_INET;
    sa.sin_addr.s_addr = htonl(INADDR_ANY);

    if ((hostName != nil) && __isString(hostName)){
	bzero(&sa, sizeof(sa)) ;
	if ((addr = inet_addr((char *) __stringVal(hostName))) != -1) {
	    /* 
	     * is Internet addr in octet notation 
	     */
	    bcopy(&addr, (char *) &sa.sin_addr, sizeof(addr)) ; /* set address */
	} else {
	    /* 
	     * do we know the host's address? 
	     */
	    GETHOSTBYNAME(hp, __stringVal(hostName))
	    if (hp == NULL) {
		DBGPRINTF(("SOCKET: unknown host: %s\n", __stringVal(hostName)));
		RETURN ( nil );
	    }
	    bcopy(hp->h_addr, (char *) &sa.sin_addr, hp->h_length) ;
	    sa.sin_family = hp->h_addrtype;
	}
    }

    /*
     * create the socket
     */
    __BEGIN_INTERRUPTABLE__
    do {
	sock = socket(sa.sin_family, SOCK_STREAM, 0);
    } while ((sock < 0) && (errno == EINTR));
    __END_INTERRUPTABLE__

    if (sock < 0) {
	DBGPRINTF(("SOCKET: socket(dom=%d typ=%d proto=0) call failed errno=%d\n", sa.sin_family, SOCK_STREAM, errno));
	__INST(lastErrorNumber) = __MKSMALLINT(errno);
    } else {
	/* 
	 * connect/bind 
	 */
	sa.sin_port = htons((u_short) _intVal(portNr)) ;

	__BEGIN_INTERRUPTABLE__
	if (hostName != nil) {
	    do {
		ret = connect(sock, (struct sockaddr *)&sa, sizeof(sa));
	    } while ((ret < 0) && (errno == EINTR));
	} else {
#ifdef SO_REUSEADDR
	    /*
	     * should I also do this for DGRAM sockets ?
	     */
	    if (setsockopt(sock, SOL_SOCKET, SO_REUSEADDR, (char *) &on, sizeof (on)) < 0) {
		DBGPRINTF(("SOCKET: setsockopt - SO_REUSEADDR failed\n"));
	    }
#endif /* SO_REUSEADDR */
	    sa.sin_addr.s_addr = htonl(INADDR_ANY);
	    do {
		ret = bind(sock, (struct sockaddr *)&sa, sizeof(sa));
	    } while ((ret < 0) && (errno == EINTR));
	}
	__END_INTERRUPTABLE__

	if (ret < 0) { 
	    DBGPRINTF(("SOCKET: bind/connect call failed errno=%d\n", errno));
	    __INST(lastErrorNumber) = __MKSMALLINT(errno);
	    __BEGIN_INTERRUPTABLE__
	    close(sock) ;
	    __END_INTERRUPTABLE__
	} else {
	    /* 
	     * make it a FILE * 
	     */
	    fp = fdopen(sock, "r+");
	    if (! fp) {
		DBGPRINTF(("SOCKET: fdopen failed\n"));
		__INST(lastErrorNumber) = __MKSMALLINT(errno);
		__BEGIN_INTERRUPTABLE__
		close(sock);
		__END_INTERRUPTABLE__
	    } else {
#ifdef BUGGY_STDIO_LIB
		setbuf(fp, NULL);
		__INST(buffered) = false;
#endif
		__INST(filePointer) = __MKOBJ(fp);
		__STORESELF(filePointer);
	    }
	}
    }
#endif
%}.
    filePointer isNil ifTrue:[
	^ nil
    ].
    mode := #readwrite.
    Lobby register:self.
    binary := false.

    domain := #inet.
    socketType := #stream.
    protocol := portNr.
    peerName := hostName.

    "
     Socket new for:'clam' port:(Socket portOfService:'echo')

     Socket new for:nil port:9999
     Socket new for:(OperatingSystem getHostName) port:9999
    "
!

for:hostName udpPort:portNr
    "setup for a UDP socket (i.e. inet domain, datagram type) 
     if hostname is nil, a server port is opened;
     otherwise a client port to the server on host.

     HISTORIC LEFTOVER:
     This method will vanish, as soon as the low level
     connect/bind works,"

    self obsoleteMethodWarning.

    filePointer notNil ifTrue:[
	^ self errorAlreadyOpen
    ].
    (portNr isMemberOf:SmallInteger) ifFalse:[
	self error:'invalid portNr'
    ].
%{
#ifndef NO_SOCKET
    struct sockaddr_in sa ;
    struct hostent *hp ;
    int a, sock ;
    long addr;
    FILE *fp;
    int ret;

    if (hostName != nil) {
	bzero(&sa, sizeof(sa)) ;
	if ((addr = inet_addr((char *) __stringVal(hostName))) != -1) {
	    /* 
	     * is Internet addr in octet notation 
	     */
	    bcopy(&addr, (char *) &sa.sin_addr, sizeof(addr)) ; /* set address */
	    sa.sin_family = AF_INET ;
	} else {
	    /* 
	     * is hostname - 
	     * do we know the host's address? 
	     */
	    GETHOSTBYNAME(hp, __stringVal(hostName))
	    if (hp == NULL) {
		DBGPRINTF(("SOCKET: unknown host: %s\n", __stringVal(hostName)));
		RETURN ( nil );
	    }
	    bcopy(hp->h_addr, (char *) &sa.sin_addr, hp->h_length) ;
	    sa.sin_family = hp->h_addrtype ;
	}
    } else {
	sa.sin_family = AF_INET;
    }

    /*
     * create the socket
     */
    __BEGIN_INTERRUPTABLE__
    do {
	sock = socket(sa.sin_family, SOCK_DGRAM, 0);
    } while ((sock < 0) && (errno == EINTR));
    __END_INTERRUPTABLE__

    if (sock < 0) {
	DBGPRINTF(("SOCKET: socket(dom=%d typ=%d proto=0) call failed errno=%d\n", sa.sin_family, SOCK_DGRAM, errno));
	__INST(lastErrorNumber) = __MKSMALLINT(errno);
    } else {
	/* 
	 * ok,
	 * connect/bind 
	 */
	__BEGIN_INTERRUPTABLE__
	if (hostName == nil) {
	    sa.sin_addr.s_addr = htonl(INADDR_ANY);
	    do {
		ret = bind(sock, (struct sockaddr *)&sa, sizeof(sa));
	    } while ((ret < 0) && (errno == EINTR));
	} else {
	    sa.sin_port = htons((u_short) _intVal(portNr)) ;
	    do {
		ret = connect(sock, (struct sockaddr *)&sa, sizeof(sa));
	    } while ((ret < 0) && (errno == EINTR));
	}
	__END_INTERRUPTABLE__

	if (ret < 0) {
	    DBGPRINTF(("SOCKET: bind/connect call failed\n"));
	    __INST(lastErrorNumber) = __MKSMALLINT(errno);
	    __BEGIN_INTERRUPTABLE__
	    close(sock) ;
	    __END_INTERRUPTABLE__
	} else {
	    /* 
	     * make it a FILE * 
	     */
	    fp = fdopen(sock, "r+");
	    if (! fp) {
		DBGPRINTF(("SOCKET: fdopen call failed\n"));
		__INST(lastErrorNumber) = __MKSMALLINT(errno);
		__BEGIN_INTERRUPTABLE__
		close(sock);
		__END_INTERRUPTABLE__
	    } else {
#ifdef BUGGY_STDIO_LIB
		setbuf(fp, NULL);
		__INST(buffered) = false;
#endif
		__INST(filePointer) = __MKOBJ(fp);
		__STORESELF(filePointer);
	    }
	}
    }
#endif
%}.
    filePointer isNil ifTrue:[
	^ nil
    ].

    mode := #readwrite.
    Lobby register:self.
    binary := false.

    domain := #inet.
    socketType := #datagram.
    protocol := portNr.
    peerName := hostName.

    "
     Socket new for:'clam' udpPort:(Socket portOfService:'echo')
    "
! !

!Socket methodsFor:'specials'!

receiveTimeout:seconds
    "set the receive timeout - for special applications only.
     Not all operatingSystems offer this functionality
     (returns false, if unsupported)"

    |millis|

    filePointer isNil ifTrue:[
	^ self errorNotOpen
    ].
    millis := (seconds * 1000) rounded.
%{
#if defined(SO_RCVTIMEO) && defined(SOL_SOCKET) && defined(HZ)
    if (__isSmallInteger(millis)) {
	OBJ fp = __INST(filePointer);
	int sock;
	int opt;

	sock = fileno(__FILEVal(fp));
	opt = _intVal(millis) / (1000 / HZ);
	setsockopt(sock, SOL_SOCKET, SO_RCVTIMEO, (char *)&opt, sizeof(int));
	RETURN(true);
    }
#endif
%}.
    ^ false
!

sendTimeout:seconds
    "set the send timeout - for special applications only.
     Not all operatingSystems offer this functionality
     (returns false, if unsupported)"

    |millis|

    filePointer isNil ifTrue:[
	^ self errorNotOpen
    ].
    millis := (seconds * 1000) rounded.
%{
#if defined(SO_SNDTIMEO) && defined(SOL_SOCKET) && defined(HZ)
    if (__isSmallInteger(millis)) {
	OBJ fp = __INST(filePointer);
	int sock;
	int opt;

	sock = fileno(__FILEVal(fp));
	opt = _intVal(millis) / (1000 / HZ);
	setsockopt(sock, SOL_SOCKET, SO_SNDTIMEO, (char *)&opt, sizeof(int));
	RETURN(true);
    }
#endif
%}.
    ^ false
! !

!Socket class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/Socket.st,v 1.133 1999-09-22 09:44:57 stefan Exp $'
! !