|
From: Andreas R. <and...@us...> - 2004-01-19 22:25:54
|
Update of /cvsroot/squeak/squeak/platforms/win32/plugins/SocketPlugin
In directory sc8-pr-cvs1:/tmp/cvs-serv18938
Modified Files:
sqWin32NewNet.c
Log Message:
Various changes throughout
Index: sqWin32NewNet.c
===================================================================
RCS file: /cvsroot/squeak/squeak/platforms/win32/plugins/SocketPlugin/sqWin32NewNet.c,v
retrieving revision 1.8
retrieving revision 1.9
diff -C2 -d -r1.8 -r1.9
*** sqWin32NewNet.c 21 Nov 2003 17:19:49 -0000 1.8
--- sqWin32NewNet.c 19 Jan 2004 22:25:51 -0000 1.9
***************
*** 154,158 ****
int sockState;
int sockError;
! int semaphoreIndex;
struct sockaddr_in peer; /* socket address in connect() or send/rcv address for UDP */
--- 154,162 ----
int sockState;
int sockError;
!
! int readSema;
! int writeSema;
! int connSema;
!
struct sockaddr_in peer; /* socket address in connect() or send/rcv address for UDP */
***************
*** 282,286 ****
setsockopt(temp->s, SOL_SOCKET, SO_LINGER, (char*)&l, sizeof(l));
closesocket(temp->s);
! temp->s = NULL;
GlobalFree(GlobalHandle(temp));
}
--- 286,290 ----
setsockopt(temp->s, SOL_SOCKET, SO_LINGER, (char*)&l, sizeof(l));
closesocket(temp->s);
! temp->s = 0;
GlobalFree(GlobalHandle(temp));
}
***************
*** 370,374 ****
printf("\n");
printf("\tError: %x\n", pss->sockError);
! printf("\tSema: %d\n", pss->semaphoreIndex);
{ /* count pending accept()s */
acceptedSocketStruct *tmp = pss->accepted;
--- 374,380 ----
printf("\n");
printf("\tError: %x\n", pss->sockError);
! printf("\treadSema: %d\n", pss->readSema);
! printf("\twriteSema: %d\n", pss->writeSema);
! printf("\tconnSema: %d\n", pss->connSema);
{ /* count pending accept()s */
acceptedSocketStruct *tmp = pss->accepted;
***************
*** 473,477 ****
struct timeval tv= { 1000, 0 }; /* Timeout value == 1000 sec */
fd_set fds;
! int n, doWait;
while(1) {
--- 479,483 ----
struct timeval tv= { 1000, 0 }; /* Timeout value == 1000 sec */
fd_set fds;
! int n, doWait, sema;
while(1) {
***************
*** 498,501 ****
--- 504,508 ----
/* Data may be available */
pss->sockState |= SOCK_DATA_READABLE;
+ SIGNAL(pss->readSema);
doWait = 1; /* until data has been read */
break;
***************
*** 504,508 ****
pss->sockState = ThisEndClosed;
pss->readWatcherOp = 0; /* since a close succeeded */
! pss->s = NULL;
doWait = 1;
break;
--- 511,516 ----
pss->sockState = ThisEndClosed;
pss->readWatcherOp = 0; /* since a close succeeded */
! pss->s = 0;
! SIGNAL(pss->connSema);
doWait = 1;
break;
***************
*** 512,515 ****
--- 520,524 ----
pss->readWatcherOp = WatchData; /* check for incoming data */
pss->writeWatcherOp = WatchData; /* and signal when writable */
+ SIGNAL(pss->connSema);
doWait = 0;
break;
***************
*** 517,529 ****
/* Connection can be accepted */
acceptHandler(pss);
doWait = 0; /* only wait for more connections */
break;
}
-
UNLOCKSOCKET(pss->mutex);
- /* Socket state changed so signal */
- SIGNAL(pss->semaphoreIndex);
} else {
! if(n != SOCKET_ERROR) {
/* select() timed out */
doWait = 0; /* continue waiting in select() */
--- 526,543 ----
/* Connection can be accepted */
acceptHandler(pss);
+ SIGNAL(pss->connSema);
doWait = 0; /* only wait for more connections */
break;
}
UNLOCKSOCKET(pss->mutex);
} else {
! if(n == SOCKET_ERROR) {
! int err = WSAGetLastError();
! LOCKSOCKET(pss->mutex, INFINITE);
! pss->sockState = OtherEndClosed;
! pss->sockError = err;
! SIGNAL(pss->connSema);
! UNLOCKSOCKET(pss->mutex);
! } else {
/* select() timed out */
doWait = 0; /* continue waiting in select() */
***************
*** 575,578 ****
--- 589,593 ----
/* asynchronous connect failed */
pss->sockState = Unconnected;
+ SIGNAL(pss->connSema);
} else {
/* get socket error */
***************
*** 580,583 ****
--- 595,599 ----
errSize = sizeof(pss->sockError);
getsockopt(pss->s, SOL_SOCKET, SO_ERROR, (char*)&pss->sockError, &errSize);
+ SIGNAL(pss->writeSema);
}
pss->writeWatcherOp = 0; /* what else can we do */
***************
*** 592,595 ****
--- 608,612 ----
pss->readWatcherOp = WatchData;
SetEvent(pss->hReadWatcherEvent);
+ SIGNAL(pss->connSema);
/* And fall through since data can be sent */
pss->writeWatcherOp = WatchData;
***************
*** 597,600 ****
--- 614,618 ----
/* Data can be sent */
pss->sockState |= SOCK_DATA_WRITABLE;
+ SIGNAL(pss->writeSema);
doWait = 1; /* until data has been written */
break;
***************
*** 602,609 ****
}
UNLOCKSOCKET(pss->mutex);
- /* Socket state changed so signal */
- SIGNAL(pss->semaphoreIndex);
} else {
! if(n != SOCKET_ERROR) {
/* select() timed out */
doWait = 0; /* continue waiting in select() */
--- 620,632 ----
}
UNLOCKSOCKET(pss->mutex);
} else {
! if(n == SOCKET_ERROR) {
! int err = WSAGetLastError();
! LOCKSOCKET(pss->mutex, INFINITE);
! pss->sockState = OtherEndClosed;
! pss->sockError = err;
! SIGNAL(pss->connSema);
! UNLOCKSOCKET(pss->mutex);
! } else {
/* select() timed out */
doWait = 0; /* continue waiting in select() */
***************
*** 807,811 ****
privateSocketStruct *pss = PSP(s);
int err;
- int failPrim = 0;
if (!SocketValid(s)) return;
--- 830,833 ----
***************
*** 823,832 ****
SetEvent(pss->hReadWatcherEvent);
} else {
pss->sockError = err;
! failPrim = 1;
}
} else {
! pss->s = NULL;
pss->sockState = Unconnected;
}
/* Cleanup any accepted sockets */
--- 845,856 ----
SetEvent(pss->hReadWatcherEvent);
} else {
+ pss->sockState = Unconnected;
pss->sockError = err;
! SIGNAL(pss->connSema);
}
} else {
! pss->s = 0;
pss->sockState = Unconnected;
+ SIGNAL(pss->connSema);
}
/* Cleanup any accepted sockets */
***************
*** 843,847 ****
}
UNLOCKSOCKET(pss->mutex);
- if(failPrim) FAIL();
}
--- 867,870 ----
***************
*** 890,902 ****
err = WSAGetLastError();
if(err != WSAEWOULDBLOCK) {
! FAIL();
! return;
}
- /* Connection in progress => Start write watcher */
- LOCKSOCKET(pss->mutex, INFINITE);
- pss->sockState = WaitingForConnection;
- pss->writeWatcherOp = WatchConnect;
- SetEvent(pss->hWriteWatcherEvent);
- UNLOCKSOCKET(pss->mutex);
} else {
/* Connection completed synchronously */
--- 913,927 ----
err = WSAGetLastError();
if(err != WSAEWOULDBLOCK) {
! pss->sockState = Unconnected; /* reset */
! pss->sockError = err;
! SIGNAL(pss->connSema);
! } else {
! /* Connection in progress => Start write watcher */
! LOCKSOCKET(pss->mutex, INFINITE);
! pss->sockState = WaitingForConnection;
! pss->writeWatcherOp = WatchConnect;
! SetEvent(pss->hWriteWatcherEvent);
! UNLOCKSOCKET(pss->mutex);
}
} else {
/* Connection completed synchronously */
***************
*** 905,908 ****
--- 930,935 ----
pss->readWatcherOp = WatchData; /* waiting for data */
SetEvent(pss->hReadWatcherEvent);
+ SIGNAL(pss->connSema);
+ SIGNAL(pss->writeSema);
UNLOCKSOCKET(pss->mutex);
}
***************
*** 954,961 ****
UDP => Just call sqListenOnPort
*****************************************************************************/
! void sqSocketListenOnPortBacklogSize(SocketPtr s, int port, int backlogSize)
{
int result;
! struct sockaddr_in addr;
privateSocketStruct *pss = PSP(s);
--- 981,993 ----
UDP => Just call sqListenOnPort
*****************************************************************************/
! void sqSocketListenOnPortBacklogSize(SocketPtr s, int port, int backlogSize) {
! sqSocketListenOnPortBacklogSizeInterface(s, port, backlogSize, 0);
! }
!
!
! void sqSocketListenOnPortBacklogSizeInterface(SocketPtr s, int port, int backlogSize, int addr)
{
int result;
! struct sockaddr_in inaddr;
privateSocketStruct *pss = PSP(s);
***************
*** 968,977 ****
/* bind the socket */
! ZeroMemory(&addr,sizeof(struct sockaddr_in));
! addr.sin_family = AF_INET;
! addr.sin_port = htons((short)port);
! addr.sin_addr.s_addr = localHostAddress;
! result = bind( SOCKET(s), (struct sockaddr*) &addr, sizeof(struct sockaddr_in));
if(result == SOCKET_ERROR) {
pss->sockError = WSAGetLastError();
--- 1000,1009 ----
/* bind the socket */
! ZeroMemory(&inaddr,sizeof(struct sockaddr_in));
! inaddr.sin_family = AF_INET;
! inaddr.sin_port = htons((short)port);
! inaddr.sin_addr.s_addr = htonl(addr);
! result = bind( SOCKET(s), (struct sockaddr*) &inaddr, sizeof(struct sockaddr_in));
if(result == SOCKET_ERROR) {
pss->sockError = WSAGetLastError();
***************
*** 995,1150 ****
/*****************************************************************************
- sqSocketCreateNetTypeSocketTypeRecvBytesSendBytesSemaID:
- Create a socket for the given netType (which is always internet here)
- a given socketType (UDP or TCP) appropriate buffer size (being ignored ;-)
- and a semaphore to signal upon changes in the socket state.
- *****************************************************************************/
- void sqSocketCreateNetTypeSocketTypeRecvBytesSendBytesSemaID(
- SocketPtr s, int netType, int socketType,
- int recvBufSize, int sendBufSize, int semaIndex)
- {
- SOCKET newSocket;
- privateSocketStruct *pss;
-
- s->sessionID = 0;
- /* perform internal initialization */
- if(socketType == TCPSocketType)
- newSocket = socket(AF_INET,SOCK_STREAM, 0);
- else if(socketType == UDPSocketType)
- newSocket = socket(AF_INET, SOCK_DGRAM, 0);
- else { FAIL(); return; }
- if(newSocket == INVALID_SOCKET) {
- FAIL();
- return;
- }
- /* Allow the re-use of the current port */
- setsockopt(newSocket, SOL_SOCKET, SO_REUSEADDR, (char*) &one, sizeof(one));
- /* Disable TCP delays */
- setsockopt(newSocket, IPPROTO_TCP, TCP_NODELAY, (char*) &one, sizeof(one));
- /* Make the socket non-blocking */
- ioctlsocket(newSocket,FIONBIO,&one);
-
- /* initialize private socket structure */
- pss = (privateSocketStruct*) calloc(1,sizeof(privateSocketStruct));
- pss->s = newSocket;
- pss->sockType = socketType;
- pss->semaphoreIndex = semaIndex;
-
- /* UDP sockets are born "connected" */
- if(UDPSocketType == socketType) {
- pss->sockState = Connected | SOCK_DATA_WRITABLE;
- } else {/* TCP */
- pss->sockState = Unconnected;
- }
- pss->sockError= 0;
-
- /* initial UDP peer := wildcard */
- ZeroMemory(&pss->peer, sizeof(pss->peer));
- pss->peer.sin_family= AF_INET;
- pss->peer.sin_port= htons((short)0);;
- pss->peer.sin_addr.s_addr= INADDR_ANY;
-
- /* fill the SQSocket */
- s->sessionID = thisNetSession;
- s->socketType = socketType;
- s->privateSocketPtr = pss;
-
- /* Create a new mutex object for synchronized access */
- pss->mutex = CreateMutex(NULL, 0,NULL);
- if(!pss->mutex) { FAIL(); return; }
-
- /* Install the socket into the socket list */
- pss->next = firstSocket;
- firstSocket = pss;
-
- /* Setup the watchers */
- if(UDPSocketType == socketType) {
- /* Since UDP sockets are always connected */
- pss->readWatcherOp = pss->writeWatcherOp = WatchData;
- }
- if(!createWatcherThreads(pss)) {
- /* note: necessary cleanup is done from within createWatcherThreads */
- s->privateSocketPtr = NULL; /* declare invalid */
- FAIL();
- }
- }
-
- /*****************************************************************************
- sqSocketAcceptFromRecvBytesSendBytesSemaID:
- Create a new socket by accepting an incoming connection from the source socket.
- *****************************************************************************/
- void sqSocketAcceptFromRecvBytesSendBytesSemaID(
- SocketPtr s, SocketPtr serverSocket,
- int recvBufSize, int sendBufSize, int semaIndex)
- {
- acceptedSocketStruct *accepted;
- privateSocketStruct *pss;
-
- /* Lock the server socket and retrieve the last accepted connection */
- pss = PSP(serverSocket); /* temporarily */
-
- /* Guard modification in server socket state */
- LOCKSOCKET(pss->mutex, INFINITE);
- accepted = pss->accepted;
- if(accepted) {
- pss->accepted = accepted->next;
- if(!pss->accepted) {
- /* No more connections; go back to waiting state and start watcher */
- pss->sockState = WaitingForConnection;
- pss->readWatcherOp = WatchAccept;
- SetEvent(pss->hReadWatcherEvent);
- }
- }
- UNLOCKSOCKET(pss->mutex);
-
- if(!accepted) { /* something was wrong here */
- FAIL();
- return;
- }
- if(accepted->s == INVALID_SOCKET) {
- FAIL();
- return;
- }
- /* private socket structure */
- pss = (privateSocketStruct*) calloc(1,sizeof(privateSocketStruct));
- pss->s = accepted->s;
- pss->sockType = PSP(serverSocket)->sockType;
- pss->semaphoreIndex = semaIndex;
- pss->sockState= Connected | SOCK_DATA_WRITABLE;
- pss->sockError= 0;
- MoveMemory(&pss->peer, &accepted->peer, sizeof(struct sockaddr_in));
-
- /* fill the SQSocket */
- s->sessionID = thisNetSession;
- s->socketType = pss->sockType;
- s->privateSocketPtr = pss;
-
- /* Disable TCP delays */
- setsockopt(SOCKET(s), IPPROTO_TCP, TCP_NODELAY, (char*) &one, sizeof(one));
- /* Make the socket non-blocking */
- ioctlsocket(SOCKET(s),FIONBIO,&one);
-
- /* Create a new mutex object for synchronized access */
- pss->mutex = CreateMutex(NULL, 0,NULL);
- if(!pss->mutex) { FAIL(); return; }
-
- /* Install the socket into the socket list */
- pss->next = firstSocket;
- firstSocket = pss;
-
- /* Setup the watchers */
- pss->readWatcherOp = pss->writeWatcherOp = WatchData;
-
- if(!createWatcherThreads(pss)) {
- /* note: necessary cleanup is done from within createWatcherThreads */
- s->privateSocketPtr = NULL; /* declare invalid */
- FAIL();
- }
-
- /* Cleanup */
- GlobalFree(GlobalHandle(accepted));
- }
-
- /*****************************************************************************
sqSocketDestroy: Release the resources associated with this socket.
If a connection is open, it is aborted
--- 1027,1030 ----
***************
*** 1204,1208 ****
int result;
int addrSize;
- int failPrim = 0;
if (!SocketValid(s)) return -1;
--- 1084,1087 ----
***************
*** 1237,1244 ****
WSock documentation this ought to be correct. */
/* UDP doesn't know "other end closed" state */
! if(pss->sockType != UDPSocketType)
pss->sockState = OtherEndClosed;
pss->sockError = err;
- failPrim = 1;
}
result = 0;
--- 1116,1124 ----
WSock documentation this ought to be correct. */
/* UDP doesn't know "other end closed" state */
! if(pss->sockType != UDPSocketType) {
pss->sockState = OtherEndClosed;
+ SIGNAL(pss->connSema);
+ }
pss->sockError = err;
}
result = 0;
***************
*** 1254,1258 ****
UNLOCKSOCKET(pss->mutex);
- if(failPrim) FAIL();
return result;
}
--- 1134,1137 ----
***************
*** 1282,1286 ****
int result;
int addrSize;
- int failPrim = 0;
if (!SocketValid(s)) return -1;
--- 1161,1164 ----
***************
*** 1320,1327 ****
WSock documentation this ought to be correct. */
/* UDP doesn't know "other end closed" state */
! if(pss->sockType != UDPSocketType)
pss->sockState = OtherEndClosed;
pss->sockError = err;
- failPrim = 1;
}
result = 0;
--- 1198,1206 ----
WSock documentation this ought to be correct. */
/* UDP doesn't know "other end closed" state */
! if(pss->sockType != UDPSocketType) {
pss->sockState = OtherEndClosed;
+ SIGNAL(pss->connSema);
+ }
pss->sockError = err;
}
result = 0;
***************
*** 1337,1341 ****
UNLOCKSOCKET(pss->mutex);
- if(failPrim) FAIL();
return result;
}
--- 1216,1219 ----
***************
*** 1417,1436 ****
/*****************************************************************************
***** New Socket Functions *****
- *****************************************************************************
- NOTE: The semantics of the 3-sema socket is currently not well-defined.
- Therefore, it is not supported.
*****************************************************************************/
! void sqSocketCreateNetTypeSocketTypeRecvBytesSendBytesSemaIDReadSemaIDWriteSemaID(
! SocketPtr s, int netType, int socketType,
! int recvBufSize, int sendBufSize, int semaIndex, int readSemaIndex, int writeSemaIndex)
{
! FAIL();
}
! void sqSocketAcceptFromRecvBytesSendBytesSemaIDReadSemaIDWriteSemaID(
! SocketPtr s, SocketPtr serverSocket,
! int recvBufSize, int sendBufSize, int semaIndex, int readSemaIndex, int writeSemaIndex)
{
! FAIL();
}
--- 1295,1466 ----
/*****************************************************************************
***** New Socket Functions *****
*****************************************************************************/
! /*****************************************************************************
! sqSocketCreateNetTypeSocketTypeRecvBytesSendBytesSemaID:
! Create a socket for the given netType (which is always internet here)
! a given socketType (UDP or TCP) appropriate buffer size (being ignored ;-)
! and a semaphore to signal upon changes in the socket state.
! *****************************************************************************/
! void sqSocketCreateNetTypeSocketTypeRecvBytesSendBytesSemaID(
! SocketPtr s, int netType, int socketType,
! int recvBufSize, int sendBufSize, int semaIndex)
{
! sqSocketCreateNetTypeSocketTypeRecvBytesSendBytesSemaIDReadSemaIDWriteSemaID(s, netType, socketType, recvBufSize, sendBufSize, semaIndex, semaIndex, semaIndex);
}
! void sqSocketCreateNetTypeSocketTypeRecvBytesSendBytesSemaIDReadSemaIDWriteSemaID(SocketPtr s, int netType, int socketType, int recvBufSize, int sendBufSize, int connSemaIndex, int readSemaIndex, int writeSemaIndex)
{
!
! SOCKET newSocket;
! privateSocketStruct *pss;
!
! s->sessionID = 0;
! /* perform internal initialization */
! if(socketType == TCPSocketType)
! newSocket = socket(AF_INET,SOCK_STREAM, 0);
! else if(socketType == UDPSocketType)
! newSocket = socket(AF_INET, SOCK_DGRAM, 0);
! else { FAIL(); return; }
! if(newSocket == INVALID_SOCKET) {
! FAIL();
! return;
! }
! /* Allow the re-use of the current port */
! setsockopt(newSocket, SOL_SOCKET, SO_REUSEADDR, (char*) &one, sizeof(one));
! /* Disable TCP delays */
! setsockopt(newSocket, IPPROTO_TCP, TCP_NODELAY, (char*) &one, sizeof(one));
! /* Make the socket non-blocking */
! ioctlsocket(newSocket,FIONBIO,&one);
!
! /* initialize private socket structure */
! pss = (privateSocketStruct*) calloc(1,sizeof(privateSocketStruct));
! pss->s = newSocket;
! pss->sockType = socketType;
! pss->connSema = connSemaIndex;
! pss->readSema = readSemaIndex;
! pss->writeSema = writeSemaIndex;
!
! /* UDP sockets are born "connected" */
! if(UDPSocketType == socketType) {
! pss->sockState = Connected | SOCK_DATA_WRITABLE;
! } else {/* TCP */
! pss->sockState = Unconnected;
! }
! pss->sockError= 0;
!
! /* initial UDP peer := wildcard */
! ZeroMemory(&pss->peer, sizeof(pss->peer));
! pss->peer.sin_family= AF_INET;
! pss->peer.sin_port= htons((short)0);;
! pss->peer.sin_addr.s_addr= INADDR_ANY;
!
! /* fill the SQSocket */
! s->sessionID = thisNetSession;
! s->socketType = socketType;
! s->privateSocketPtr = pss;
!
! /* Create a new mutex object for synchronized access */
! pss->mutex = CreateMutex(NULL, 0,NULL);
! if(!pss->mutex) { FAIL(); return; }
!
! /* Install the socket into the socket list */
! pss->next = firstSocket;
! firstSocket = pss;
!
! /* Setup the watchers */
! if(UDPSocketType == socketType) {
! /* Since UDP sockets are always connected */
! pss->readWatcherOp = pss->writeWatcherOp = WatchData;
! }
! if(!createWatcherThreads(pss)) {
! /* note: necessary cleanup is done from within createWatcherThreads */
! s->privateSocketPtr = NULL; /* declare invalid */
! FAIL();
! }
! }
!
!
! /*****************************************************************************
! sqSocketAcceptFromRecvBytesSendBytesSemaID:
! Create a new socket by accepting an incoming connection from the source socket.
! *****************************************************************************/
!
! void sqSocketAcceptFromRecvBytesSendBytesSemaID(
! SocketPtr s, SocketPtr serverSocket,
! int recvBufSize, int sendBufSize, int semaIndex)
! {
! sqSocketAcceptFromRecvBytesSendBytesSemaIDReadSemaIDWriteSemaID(s, serverSocket, recvBufSize, sendBufSize, semaIndex, semaIndex, semaIndex);
! }
!
! void sqSocketAcceptFromRecvBytesSendBytesSemaIDReadSemaIDWriteSemaID(SocketPtr s, SocketPtr serverSocket, int recvBufSize, int sendBufSize, int connSemaIndex, int readSemaIndex, int writeSemaIndex)
! {
! acceptedSocketStruct *accepted;
! privateSocketStruct *pss;
!
! /* Lock the server socket and retrieve the last accepted connection */
! pss = PSP(serverSocket); /* temporarily */
!
! /* Guard modification in server socket state */
! LOCKSOCKET(pss->mutex, INFINITE);
! accepted = pss->accepted;
! if(accepted) {
! pss->accepted = accepted->next;
! if(!pss->accepted) {
! /* No more connections; go back to waiting state and start watcher */
! pss->sockState = WaitingForConnection;
! pss->readWatcherOp = WatchAccept;
! SetEvent(pss->hReadWatcherEvent);
! }
! }
! UNLOCKSOCKET(pss->mutex);
!
! if(!accepted) { /* something was wrong here */
! FAIL();
! return;
! }
! if(accepted->s == INVALID_SOCKET) {
! FAIL();
! return;
! }
! /* private socket structure */
! pss = (privateSocketStruct*) calloc(1,sizeof(privateSocketStruct));
! pss->s = accepted->s;
! pss->sockType = PSP(serverSocket)->sockType;
! pss->connSema = connSemaIndex;
! pss->readSema = readSemaIndex;
! pss->writeSema = writeSemaIndex;
! pss->sockState= Connected | SOCK_DATA_WRITABLE;
! pss->sockError= 0;
! MoveMemory(&pss->peer, &accepted->peer, sizeof(struct sockaddr_in));
!
! /* fill the SQSocket */
! s->sessionID = thisNetSession;
! s->socketType = pss->sockType;
! s->privateSocketPtr = pss;
!
! /* Disable TCP delays */
! setsockopt(SOCKET(s), IPPROTO_TCP, TCP_NODELAY, (char*) &one, sizeof(one));
! /* Make the socket non-blocking */
! ioctlsocket(SOCKET(s),FIONBIO,&one);
!
! /* Create a new mutex object for synchronized access */
! pss->mutex = CreateMutex(NULL, 0,NULL);
! if(!pss->mutex) { FAIL(); return; }
!
! /* Install the socket into the socket list */
! pss->next = firstSocket;
! firstSocket = pss;
!
! /* Setup the watchers */
! pss->readWatcherOp = pss->writeWatcherOp = WatchData;
!
! if(!createWatcherThreads(pss)) {
! /* note: necessary cleanup is done from within createWatcherThreads */
! s->privateSocketPtr = NULL; /* declare invalid */
! FAIL();
! }
!
! /* Cleanup */
! GlobalFree(GlobalHandle(accepted));
}
***************
*** 1441,1445 ****
return interpreterProxy->primitiveFail();
/* bind UDP socket*/
! sqSocketConnectToPort(s, address, port);
if(interpreterProxy->failed()) return 0;
/* receive data */
--- 1471,1475 ----
return interpreterProxy->primitiveFail();
/* bind UDP socket*/
! sqSocketConnectToPort(s, *address, *port);
if(interpreterProxy->failed()) return 0;
/* receive data */
***************
*** 1629,1633 ****
if (opt->optType == 1) {
len= sizeof(optval);
! if ((getsockopt(SOCKET(s), opt->optLevel, opt->optName,&optval, &len)) < 0)
{
/* printf("getsockopt() returned < 0\n"); */
--- 1659,1664 ----
if (opt->optType == 1) {
len= sizeof(optval);
! if ((getsockopt(SOCKET(s), opt->optLevel, opt->optName,
! (void*)&optval,&len)) < 0)
{
/* printf("getsockopt() returned < 0\n"); */
|