Socket.st
author claus
Thu, 10 Aug 1995 20:36:43 +0200
changeset 85 df13b436b54e
parent 84 d401ce0001dc
child 91 01e72b1e93de
permissions -rw-r--r--
.

"
 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 comment:'
COPYRIGHT (c) 1992 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libbasic2/Socket.st,v 1.27 1995-08-10 18:36:21 claus Exp $
'!

!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.
"
!

version
"
$Header: /cvs/stx/stx/libbasic2/Socket.st,v 1.27 1995-08-10 18:36:21 claus Exp $
"
!

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

    Also, currently there is almost no support for other than IP 
    sockets - this will be added in the future.
    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 interface,
    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 erc; 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.
"
!

examples
"
    example (get help info from an nntp server):

	|sock|

	sock := Socket 
		    newTCPclientToHost:(OperatingSystem 
					    getEnvironment:'NNTPSERVER') 
				  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


    example (connect to an ftp server):

	|sock|

	sock := Socket 
		    newTCPclientToHost:(OperatingSystem getHostName) 
				  port:'ftp'.

	sock buffered:false.
	Transcript showCr:sock nextLine.
	sock nextPutAll:('USER ' , OperatingSystem getLoginName); cr.
	Transcript showCr:sock nextLine.
	sock nextPutAll:('PASS ' , 'your password here'); cr.
	Transcript showCr:sock nextLine.
	sock nextPutAll:'LIST'; cr.
	Transcript showCr:sock nextLine.

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


    example (connect to an snmp server):

	|sock port|

	sock := Socket newUDP.
	port := Socket portOfService:'snmp'.
	sock connectTo:(OperatingSystem getHostName) port:port.
	sock buffered:false.
	Transcript showCr:'got it'.

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

	|connectSock sock|

	connectSock := Socket provide:9996.  
	Transcript showCr:'listen ..'.
	connectSock listenFor:5.
	Transcript showCr:'wait'.
	connectSock readWait.  
	Transcript showCr:'accept'.
	sock := Socket new acceptOn:self.
	Transcript showCr:'close'.
	connectSock close.
	sock buffered:false.
	Transcript showCr:'server: got it'.
	'can now do transfer via sock'.
	Transcript showCr:'read'.
	Transcript showCr:('got: ' , sock nextLine).
	sock close

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

	|sock|

	sock := Socket connectTo:9996 on:'porty'.
	sock buffered:false.
	Transcript showCr:'client: got it'.
	'can now do transfer via sock'.
	Transcript showCr:'sending <hello>'.
	sock nextPutLine:'hello'.
	sock close
"
! !

!Socket primitiveDefinitions!

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

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

#ifndef transputer
# include <fcntl.h>
# include <sys/types.h>
# ifdef IRIS
   /* no socket.h on 4.0.5h ?!?!? */
#  define AF_UNIX 1
#  define AF_INET 2
#  define SOCK_STREAM 1
#  define SOCK_DGRAM  2
#  define SOCK_RAW    3
# else
#  include <sys/socket.h>
# endif
# include <netdb.h>
# include <netinet/in.h>
# if ! (defined(SYSV3) && defined(mc88k))
#  include <netinet/tcp.h>
# endif
#endif

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

static int __debugging__ = 0;

#ifdef DEBUG
# define DBGPRINTF(x)    printf x
#else
# define DBGPRINTF(x)    /* as nothing */
#endif

%}
! !

!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 class methodsFor:'queries'!

ipAddressOfHost:aHostName
    "return the IP (internet-) number for a hostname"

    |b1 b2 b3 b4|

%{
    struct sockaddr_in sa ;
    struct hostent *hp ;
    long addr;

    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? */
	    if ((hp = gethostbyname((char *) _stringVal(aHostName))) == NULL) {
		DBGPRINTF(("unknown host\n"));
		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) {
	RETURN ( nil );
    }
    b1 = _MKSMALLINT((sa.sin_addr.s_addr >> 24) & 0xFF);
    b2 = _MKSMALLINT((sa.sin_addr.s_addr >> 16) & 0xFF);
    b3 = _MKSMALLINT((sa.sin_addr.s_addr >> 8) & 0xFF);
    b4 = _MKSMALLINT((sa.sin_addr.s_addr >> 0) & 0xFF);
%}
.
    ^ ByteArray with:b1 with:b2 with:b3 with:b4

    "
     Socket ipAddressOfHost:'clam'
     Socket ipAddressOfHost:'porty'
     Socket ipAddressOfHost:'josef'
     Socket ipAddressOfHost:'styx.com'
    "
!

hostWithIpAddress:anAddress
    "return the hostname for an IP (internet-) address"

    |b1 b2 b3 b4|

    b1 := anAddress at:1.
    b2 := anAddress at:2.
    b3 := anAddress at:3.
    b4 := anAddress at:4.
%{
    struct sockaddr_in sa ;
    struct hostent *hp ;

    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_family = AF_INET;
	/* do we know the host's address? */
	hp = gethostbyaddr((char *) &sa.sin_addr.s_addr, sizeof(sa.sin_addr.s_addr), AF_INET);
	if (hp == NULL) {
	    DBGPRINTF(("unknown 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 COMMA_CON));

    RETURN (_MKSTRING(inet_ntoa(sa.sin_addr) COMMA_CON));
%}

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

portOfService:aNameOrNumber
    "returns the port-number for a given service
     or nil if no such service exists;
     - used to convert service names to portNumbers"
%{
    struct servent *servent = NULL;

    if (__isSmallInteger(aNameOrNumber)) {
	servent = getservbyport(htons(_intVal(aNameOrNumber)), "tcp") ;
	if (servent != NULL) {
	    RETURN ( aNameOrNumber );
	}
	RETURN ( aNameOrNumber );
    }
    if (__isString(aNameOrNumber)) {
	servent = getservbyname((char *) _stringVal(aNameOrNumber), "tcp");
	if (servent != NULL) {
	    RETURN ( _MKSMALLINT(ntohs(servent->s_port)) );
	}
	RETURN ( nil );
    }
    RETURN ( nil );
%}
    "
     Socket portOfService:'finger'
     Socket portOfService:'nntp'  
     Socket portOfService:'echo' 
     Socket portOfService:'snmp' 
    "
!

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

    if (__isSmallInteger(aNameOrNumber)) {
	servent = getservbyport(htons(_intVal(aNameOrNumber)), "tcp") ;
	if (servent == NULL) {
	    servent = getservbyport(htons(_intVal(aNameOrNumber)), "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 COMMA_CON) );
    }
    RETURN ( nil );
%}
    "
     Socket protocolOfService:'finger' 
     Socket protocolOfService:'nntp'  
     Socket protocolOfService:'xxx'
     Socket protocolOfService:79
     Socket protocolOfService:'snmp' 
    "
!

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].

    "
     x25 stuff (if any)
     appletalk stuff (if any)
     other stuff (if any)
    "
    ^ nil

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

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].
    "
     x25 stuff (if any)
     appletalk stuff (if any)
     other stuff (if any)
    "
    ^ nil

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

!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 system will 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:'ST80 queries'!

sockStream
    "return the type code for stream sockets"

    ^ #stream
! !

!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 domain 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:'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, #ns, #appletalk or #ns;
     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
    "
!

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
    ].
    ^ newSock

    "Socket newUDP:nil"
!

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
    ].
    ^ newSock


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

newTCPclientToHost:hostname port:aService
    "create a new TCP client socket connecting to a service."

    |newSock|

    newSock := self newTCP.
    newSock notNil ifTrue:[
	(newSock connectTo:hostname port:(self portOfService:aService)) ifFalse:[
	    ^ nil
	]
    ].
    ^ newSock
"
same as:
    ^ (self new) for:hostname port:(self portOfService:aPort).
"
    "
      Socket newTCPclientToHost:'slsv6bt' port:'nntp'
    "
!

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
"
!

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
"
! !

!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."

    |errorNr|

    filePointer notNil ifTrue:[
	^ self error:'already created'
    ].
%{
    FILE *fp;
    int dom, typ, proto, sock;

    if (! __isSymbol(domainArg)) { 
	DBGPRINTF(("bad domain\n"));
	RETURN ( nil );
    }
    if (! __isSymbol(typeArg)) { 
	DBGPRINTF(("bad type\n"));
	RETURN ( nil );
    }

    /*
     * get address-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_NS
    if (domainArg == @symbol(ns))
	dom = AF_NS;
    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
    {
	DBGPRINTF(("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(("bad type <%s>\n", _stringVal(typeArg)));
	RETURN ( nil );
    }

    __BEGIN_INTERRUPTABLE__
    do {
printf("opening socket type=%d\n", typ);
	sock = socket(dom, typ, 0);
    } while ((sock < 0) && (errno == EINTR));
    __END_INTERRUPTABLE__

    if (sock < 0) {
	DBGPRINTF(("socket call failed\n"));
	_INST(lastErrorNumber) = _MKSMALLINT(errno);
    } else {
	/* 
	 * make it a FILE * 
	 */
	fp = fdopen(sock, "r+");
	if (! fp) {
	    DBGPRINTF(("fdopen call failed\n"));
	    _INST(lastErrorNumber) = _MKSMALLINT(errno);
	    __BEGIN_INTERRUPTABLE__
	    close(sock);
	    __END_INTERRUPTABLE__
	} else {
	    _INST(filePointer) = MKOBJ(fp);
	}
    }
%}
.
    "all ok?"
    filePointer notNil ifTrue:[
	domain := domainArg.
	socketType := typeArg.
    ] ifFalse:[
	^ nil
    ].

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

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 error:'already created'
    ].
    (portNr isMemberOf:SmallInteger) ifFalse:[
	^ self error:'invalid portNr'
    ].
%{
    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? 
	     */
	    if ((hp = gethostbyname((char *) _stringVal(hostName))) == NULL) {
		DBGPRINTF(("unknown host\n"));
		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 call failed\n"));
	_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(("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(("fdopen call failed\n"));
		_INST(lastErrorNumber) = _MKSMALLINT(errno);
		__BEGIN_INTERRUPTABLE__
		close(sock);
		__END_INTERRUPTABLE__
	    } else {
/*
		setbuf(fp, NULL);
 */
		_INST(filePointer) = MKOBJ(fp);
	    }
	}
    }
%}.
    filePointer isNil ifTrue:[
	^ nil
    ].

"
    buffered := false.
"
    mode := #readwrite.
    binary := false.

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

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

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 error:'already created'
    ].
    (portNr isMemberOf:SmallInteger) ifFalse:[
	^ self error:'invalid portNr'
    ].
%{
    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? 
	     */
	    if ((hp = gethostbyname((char *) _stringVal(hostName))) == NULL) {
		DBGPRINTF(("unknown host\n"));
		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 call failed\n"));
	_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(("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(("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(("fdopen failed\n"));
		_INST(lastErrorNumber) = _MKSMALLINT(errno);
		__BEGIN_INTERRUPTABLE__
		close(sock);
		__END_INTERRUPTABLE__
	    } else {
/*
		setbuf(fp, NULL);
*/
		_INST(filePointer) = MKOBJ(fp);
	    }
	}
    }
%}.
    filePointer isNil ifTrue:[
	^ nil
    ].
"
    buffered := false.
"
    mode := #readwrite.
    binary := false.

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

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

!Socket methodsFor:'low level'!

closeFile
    "low level close"

%{  /* NOCONTEXT */

    OBJ t;

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

	fp = MKFD(t);
	fflush(fp);
	shutdown(fileno(fp), 2);
	fclose(fp);
	_INST(filePointer) = nil;
    }
%}
!

bindTo:aSocketAddress 
    "ST80 compatible bind:
     the socketAddress object is supposed to respond to
     portOrName and address requests."

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

bindTo:portNrOrName address:address
    "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 uses (4byte) byteArray like internet numbers,
	unix uses pathname strings,
	others use whatever will come up in the future
     "

    filePointer isNil ifTrue:[
	^ self error:'not a valid socket'
    ].
%{
    OBJ t = _INST(filePointer);
    OBJ myDomain;
    int sock;
    struct sockaddr_in insock;
    int ret;
    int on = 1;
    int ok;
    extern OBJ LargeInteger;

    if (!__isString(_INST(domain)) && !__isSymbol(_INST(domain))) {
	DBGPRINTF(("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
	 */
	insock.sin_family = AF_INET;
	if (! __isSmallInteger(portNrOrName)) {
	    DBGPRINTF(("invalid port arg\n"));
	    RETURN (false);
	}
	insock.sin_port = htons((u_short) _intVal(portNrOrName));
	if (address == nil) {
	    insock.sin_addr.s_addr = htonl(INADDR_ANY);
	    ok = 1;
	} else {
	    if (__isInteger(address)) {
		insock.sin_addr.s_addr = htonl(__longIntVal(address));
		ok = 1;
	    } else {
		printf("SOCKET: address bind not yet supported\n");
		RETURN (false);
	    }
	}
    }
#endif
    /*
     * XXXX add addressing stuff for other domains here ...
     */
#ifdef AF_UNIX
    if (myDomain == @symbol(unix)) {
    }
#endif
#ifdef AF_X25
    if (myDomain == @symbol(x25)) {
    }
#endif
#ifdef AF_NS
    if (myDomain == @symbol(ns)) {
    }
#endif
#ifdef AF_APPLETALK
    if (myDomain == @symbol(appletalk)) {
    }
#endif

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

    sock = fileno(MKFD(t));

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

    do {
	ret = bind(sock, (struct sockaddr *)&insock, sizeof(insock));
    } while ((ret < 0) && (errno == EINTR));

    if (ret < 0) {
	DBGPRINTF(("bind failed\n"));
	_INST(lastErrorNumber) = _MKSMALLINT(errno);
	RETURN (false);
    }
%}.

    port := portNrOrName.
    ^ true

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

connectTo:hostName port:portNrOrName
    "low level connect; connect to port, portNrOrName on host, hostName.
     Return true if ok, false otherwise.
     Hostname must be a string, portNrOrName an integer port number (in inet domain)."

    filePointer isNil ifTrue:[
	^ self error:'not a valid socket'
    ].
%{
    OBJ t = _INST(filePointer);
    OBJ myDomain;
    struct sockaddr_in sa ;
    struct hostent *hp ;
    int a, sock ;
    long addr;
    FILE *fp;
    int ret;
    int on = 1;
    int ok;

    if (! __isString(hostName)) {
	DBGPRINTF(("invalid hostname arg\n"));
	RETURN (false);
    }
    if (!__isString(_INST(domain)) && !__isSymbol(_INST(domain))) {
	DBGPRINTF(("invalid domain arg\n"));
	RETURN (false);
    }

    ok = 0;
    myDomain = _INST(domain);
#ifdef AF_INET
    if (myDomain == @symbol(inet)) {
	if (! __isSmallInteger(portNrOrName)) {
	    DBGPRINTF(("invalid port arg\n"));
	    RETURN (false);
	}

	bzero((char *) &sa, sizeof(sa)) ;
	sa.sin_family = AF_INET;
	sa.sin_port = htons((u_short) _intVal(portNrOrName)) ;

	if ((addr = inet_addr((char *) _stringVal(hostName))) != -1) {
	    /* 
	     * is Internet addr in octet notation 
	     */
	    bcopy(&addr, (char *) &sa.sin_addr, sizeof(addr)) ; /* set address */
	    ok = 1;
	} else {
	    /* 
	     * do we know the host's address? 
	     */
	    if ((hp = gethostbyname((char *) _stringVal(hostName))) == NULL) {
		DBGPRINTF(("unknown host:%s\n", _stringVal(hostName)));
		RETURN (false);
	    }
	    bcopy(hp->h_addr, (char *) &sa.sin_addr, hp->h_length) ;
	    sa.sin_family = hp->h_addrtype;
	    ok = 1;
	}
    }
#endif
    /*
     * XXXX add addressing stuff for other domains here ...
     */
#ifdef AF_UNIX
    if (myDomain == @symbol(unix)) {
    }
#endif
#ifdef AF_X25
    if (myDomain == @symbol(x25)) {
    }
#endif
#ifdef AF_NS
    if (myDomain == @symbol(ns)) {
    }
#endif
#ifdef AF_APPLETALK
    if (myDomain == @symbol(appletalk)) {
    }
#endif

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

    sock = fileno(MKFD(t));

    /* 
     * connect 
     */
    __BEGIN_INTERRUPTABLE__

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

    if (ret < 0) { 
	DBGPRINTF(("connect failed\n"));
	_INST(lastErrorNumber) = _MKSMALLINT(errno);
	RETURN (false);
    }
%}.
    port := portNrOrName.
    ^ true
!

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

    filePointer isNil ifTrue:[
	^ self error:'not a valid socket'
    ].
%{
    OBJ fp = _INST(filePointer);
    int sock;
    int ret;

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

    sock = fileno(MKFD(fp));

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

    if (ret < 0) {
	DBGPRINTF(("listen call failed\n"));
	_INST(lastErrorNumber) = _MKSMALLINT(errno);
	RETURN (false);
    }
%}.
    ^ true
!

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

    ^ self listenWithBacklog:aNumber
!

acceptOn: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 error:'already connected'
    ].

    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'
    ].
%{
    FILE *fp;
    int flags;
    int sock, newSock;
    struct sockaddr_in sa ;
    int alen;
    struct hostent *he ;
    char dotted[20] ;

    alen = sizeof(sa) ;
    sock = _intVal(serverSocketFd);

    flags = ioctl(sock, F_GETFL, 0);
    ioctl(sock, F_SETFL, flags | O_NDELAY);
    __BEGIN_INTERRUPTABLE__
    do {
	newSock = accept(sock, (struct sockaddr *) &sa, &alen);
    } while ((newSock < 0) && (errno == EINTR));
    __END_INTERRUPTABLE__

    if (newSock < 0) {
	DBGPRINTF(("accept call failed\n"));
	_INST(lastErrorNumber) = _MKSMALLINT(errno);
	RETURN (false);
    }

    /*
     * extract the partners address
     */
#ifdef AF_INET
    if (_INST(domain) == @symbol(inet)) {
	he = gethostbyaddr((char *) &sa.sin_addr.s_addr, alen, AF_INET) ;
	if (! he) {
	    unsigned long norder;

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

    /* 
     * make it a FILE * 
     */
    fp = fdopen(newSock, "r+");
    if (! fp) {
	DBGPRINTF(("fdopen call failed\n"));
	_INST(lastErrorNumber) = _MKSMALLINT(errno);
	close(newSock);
	RETURN (false);
    } else {
/*
	setbuf(fp, NULL);
*/
	_INST(filePointer) = MKOBJ(fp);
    }
%}.
"
    buffered := false.
"
    mode := #readwrite.
    binary := false.
    port := aSocket port.
    ^ true
!

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|

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

    "
     |sock newSock|

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

!Socket methodsFor:'queries'!

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

    ^ peerName
!

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

    ^ port printString
!

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

    ^ port
!

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

    ^ domain
!

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

    ^ socketType
!

isActive
    ^ filePointer notNil
! !

!Socket methodsFor:'ST-80 mimicri'!

errorReporter
    ^ self
!

notReadySignal
    "for now - this is not yet raised"

    ^ Signal new
! !

!Socket methodsFor:'specials'!

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 error:'not a valid socket'
    ].
    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(MKFD(fp));
	opt = _intVal(millis) / (1000 / HZ);
	setsockopt(sock, SOL_SOCKET, SO_SNDTIMEO, (char *)&opt, sizeof(int));
	RETURN(true);
    }
#endif
%}.
    ^ false
!

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 error:'not a valid socket'
    ].
    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(MKFD(fp));
	opt = _intVal(millis) / (1000 / HZ);
	setsockopt(sock, SOL_SOCKET, SO_RCVTIMEO, (char *)&opt, sizeof(int));
	RETURN(true);
    }
#endif
%}.
    ^ false
! !

!Socket methodsFor:'datagram transmission'!

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."

    |addrBytes addrLen nReceived|

    addrBytes := ByteArray new:100.
%{
    OBJ oClass;
    OBJ fp = _INST(filePointer);
    int nInstVars, nInstBytes, objSize;
    int sock;
    struct sockaddr_in sa ;
    int alen;
    int n;
    char *cp;
    int flags = 0;

    if (fp != nil) {
	sock = fileno((FILE *)(_intVal(fp)));

	oClass = __Class(aDataBuffer);
	switch (_intVal(_ClassInstPtr(oClass)->c_flags) & ARRAYMASK) {
	    case BYTEARRAY:
	    case WORDARRAY:
	    case LONGARRAY:
	    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;
		bcopy((char *)&sa, cp, alen);
		addrLen = _MKSMALLINT(alen);
	    }
	}
	if (n < 0) {
	    _INST(lastErrorNumber) = _MKSMALLINT(errno);
	}
	nReceived = _MKSMALLINT(n);
    }
bad: ;
%}.
    nReceived notNil ifTrue:[
	nReceived < 0 ifTrue:[
	    (OperatingSystem errorTextForNumber:lastErrorNumber) printNL.
	].
	addrLen notNil ifTrue:[
	    anAddressBuffer class isBytes ifTrue:[
		anAddressBuffer replaceFrom:1 to:addrLen with:addrBytes
	    ] ifFalse:[
		"/ can be SocketAddress for ST-80 compatibility
		anAddressBuffer addressBytes:(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
!

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)
!

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: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 6-byte byteArray (last 2 bytes are portNo, msb-first)
    "/ or an instance of IPSocketAddress
    "/
    anAddressBuffer class isBytes ifTrue:[
	addrBytes := anAddressBuffer copyFrom:1 to:4.
	portNo := ((anAddressBuffer at:5) bitShift:8)
		  + (anAddressBuffer at:6).
    ] ifFalse:[
	addrBytes := anAddressBuffer hostAddress.
	portNo := anAddressBuffer port.
    ].
%{
    OBJ oClass;
    OBJ fp = _INST(filePointer);
    int nInstVars, nInstBytes, objSize;
    int sock;
    struct sockaddr_in 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((FILE *)(_intVal(fp)));

	if (addrBytes != nil) {
	    if (! __isByteArray(addrBytes)) goto bad;
	    cp = __ByteArrayInstPtr(addrBytes)->ba_element;
	    n = __byteArraySize(addrBytes);
	    if (alen < n) n = alen;
/*
printf("address is %d bytes ... %d.%d.%d.%d", n, cp[0], cp[1], cp[2], cp[3]);
*/
	    bcopy(cp, &sa.sin_addr.s_addr, n);
	    sa.sin_family = AF_INET;
	    sa.sin_port = htons((u_short) __intVal(portNo)); 
	} else {
	    alen = 0;
	    saPtr = (struct sockaddr *)0;
	}

	oClass = __Class(aDataBuffer);
	switch (_intVal(_ClassInstPtr(oClass)->c_flags) & ARRAYMASK) {
	    case BYTEARRAY:
		offs = __intVal(startIndex) - 1;
		break;
	    case WORDARRAY:
		offs = (__intVal(startIndex) - 1) * sizeof(short);
		break;
	    case LONGARRAY:
		offs = (__intVal(startIndex) - 1) * sizeof(long);
		break;
	    case FLOATARRAY:
		offs = (__intVal(startIndex) - 1) * sizeof(float);
		break;
	    case DOUBLEARRAY:
		offs = (__intVal(startIndex) - 1) * sizeof(double);
#ifdef NEED_DOUBLE_ALIGN
		offs += sizeof(long);
#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) {
/*
printf("cut off ...\n");
*/
	    nBytes = objSize - offs;
	}

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

	__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));
    }
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
! !