1 /***********************************************************************
2  *
3  *      C interface to BSD sockets.
4  *
5  *
6  ***********************************************************************/
7 
8 /***********************************************************************
9  *
10  * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2007,2008,2009
11  * Free Software Foundation, Inc.
12  * Written by Steve Byrne and Paolo Bonzini.
13  *
14  * This file is part of GNU Smalltalk.
15  *
16  * GNU Smalltalk is free software; you can redistribute it and/or modify it
17  * under the terms of the GNU General Public License as published by the Free
18  * Software Foundation; either version 2, or (at your option) any later
19  * version.
20  *
21  * Linking GNU Smalltalk statically or dynamically with other modules is
22  * making a combined work based on GNU Smalltalk.  Thus, the terms and
23  * conditions of the GNU General Public License cover the whole
24  * combination.
25  *
26  * In addition, as a special exception, the Free Software Foundation
27  * give you permission to combine GNU Smalltalk with free software
28  * programs or libraries that are released under the GNU LGPL and with
29  * independent programs running under the GNU Smalltalk virtual machine.
30  *
31  * You may copy and distribute such a system following the terms of the
32  * GNU GPL for GNU Smalltalk and the licenses of the other code
33  * concerned, provided that you include the source code of that other
34  * code when and as the GNU GPL requires distribution of source code.
35  *
36  * Note that people who make modified versions of GNU Smalltalk are not
37  * obligated to grant this special exception for their modified
38  * versions; it is their choice whether to do so.  The GNU General
39  * Public License gives permission to release a modified version without
40  * this exception; this exception also makes it possible to release a
41  * modified version which carries forward this exception.
42  *
43  * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT
44  * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
45  * FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License for
46  * more details.
47  *
48  * You should have received a copy of the GNU General Public License along with
49  * GNU Smalltalk; see the file COPYING.  If not, write to the Free Software
50  * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
51  *
52  ***********************************************************************/
53 
54 #include "gstpriv.h"
55 
56 #include <signal.h>
57 #include <fcntl.h>
58 #include <errno.h>
59 
60 #ifdef HAVE_UNISTD_H
61 #include <unistd.h>
62 #endif
63 
64 #if __STDC__
65 #include <string.h>
66 #include <stdlib.h>
67 #endif /* STDC_HEADERS */
68 
69 #include <stdio.h>
70 #include <errno.h>
71 
72 #ifdef HAVE_SYS_UTSNAME_H
73 #include <sys/utsname.h>
74 #endif
75 
76 #ifdef HAVE_SOCKETS
77 
78 #ifndef ntohl
79 #if WORDS_BIGENDIAN
80 #define ntohl(x) (x)
81 #define ntohs(x) (x)
82 #else
83 #define ntohl(x) \
84         ((unsigned long int)((((unsigned long int)(x) & 0x000000ffU) << 24) | \
85                              (((unsigned long int)(x) & 0x0000ff00U) <<  8) | \
86                              (((unsigned long int)(x) & 0x00ff0000U) >>  8) | \
87                              (((unsigned long int)(x) & 0xff000000U) >> 24)))
88 
89 #define ntohs(x) \
90         ((unsigned short int)((((unsigned short int)(x) & 0x00ff) << 8) | \
91                               (((unsigned short int)(x) & 0xff00) >> 8)))
92 #endif
93 #endif /* ntohl */
94 
95 
96 
97 
98 static char *
myGetHostByAddr(char * addr,int len,int type)99 myGetHostByAddr (char *addr, int len, int type)
100 {
101   struct hostent *hostEnt;
102   char *result;
103 
104 #if HAVE_GETIPNODEBYADDR
105   int error;
106   hostEnt = getipnodebyaddr (addr, len, type, &error);
107 #else
108   hostEnt = gethostbyaddr (addr, len, type);
109 #endif
110 
111   if (hostEnt)
112     {
113       result = malloc (128);	/* out of a hat */
114       strncpy (result, hostEnt->h_name, 128);
115 #if HAVE_GETIPNODEBYADDR
116       freehostent (hostEnt);
117 #endif
118     }
119   else
120     result = NULL;
121 
122   return (result);
123 }
124 
125 /* The offsets of these two fields are not portable.  */
126 
127 static char **
get_aiCanonname(struct addrinfo * ai)128 get_aiCanonname (struct addrinfo *ai)
129 {
130   return &ai->ai_canonname;
131 }
132 
133 static struct sockaddr **
get_aiAddr(struct addrinfo * ai)134 get_aiAddr (struct addrinfo *ai)
135 {
136   return &ai->ai_addr;
137 }
138 
139 static char *
myGetHostName(void)140 myGetHostName (void)
141 {
142   char *result;
143 
144   result = malloc (128);
145 #ifdef HAVE_UNAME
146   {
147     struct utsname utsname;
148     int ret;
149 
150     ret = uname (&utsname);
151     if (ret < 0)
152       return NULL;
153 
154     strncpy (result, utsname.nodename, 128);
155     result[127] = '\0';
156   }
157 #else
158 #ifdef HAVE_GETHOSTNAME
159   {
160     extern int gethostname ();
161     gethostname (result, 128);
162   }
163 #else
164   strcpy (result, "localhost");	/* terrible guess */
165 #endif
166 #endif
167   return (result);
168 }
169 
170 #define constantFunction(name, constant) \
171   static long name(void) { return (constant); }
172 
173 constantFunction (afUnspec, AF_UNSPEC);
174 constantFunction (afInet, AF_INET);
175 constantFunction (afUnix, AF_UNIX);
176 constantFunction (pfUnspec, PF_UNSPEC);
177 constantFunction (pfInet, PF_INET);
178 constantFunction (pfUnix, PF_UNIX);
179 constantFunction (msgOOB, MSG_OOB);
180 constantFunction (msgPeek, MSG_PEEK);
181 constantFunction (solSocket, SOL_SOCKET);
182 constantFunction (soLinger, SO_LINGER);
183 constantFunction (soReuseAddr, SO_REUSEADDR);
184 constantFunction (sockStream, SOCK_STREAM);
185 constantFunction (sockRaw, SOCK_RAW);
186 constantFunction (sockRDM, SOCK_RDM);
187 constantFunction (sockDgram, SOCK_DGRAM);
188 constantFunction (ipprotoIcmp, IPPROTO_ICMP);
189 constantFunction (ipprotoUdp, IPPROTO_UDP);
190 constantFunction (ipprotoTcp, IPPROTO_TCP);
191 constantFunction (ipprotoIp, IPPROTO_IP);
192 constantFunction (tcpNodelay, TCP_NODELAY);
193 
194 #ifdef HAVE_IPV6
195 constantFunction (afInet6, AF_INET6);
196 constantFunction (pfInet6, PF_INET6);
197 constantFunction (ipprotoIcmpv6, IPPROTO_ICMPV6);
198 #else
199 constantFunction (afInet6, -1);
200 constantFunction (pfInet6, -1);
201 constantFunction (ipprotoIcmpv6, -1);
202 #endif
203 
204 #ifdef IP_MULTICAST_TTL
205 constantFunction (ipMulticastTtl, IP_MULTICAST_TTL);
206 constantFunction (ipMulticastIf, IP_MULTICAST_IF);
207 constantFunction (ipAddMembership, IP_ADD_MEMBERSHIP);
208 constantFunction (ipDropMembership, IP_DROP_MEMBERSHIP);
209 #else
210 constantFunction (ipMulticastTtl, -1);
211 constantFunction (ipMulticastIf, -1);
212 constantFunction (ipAddMembership, -1);
213 constantFunction (ipDropMembership, -1);
214 #endif
215 
216 #ifndef AI_ADDRCONFIG
217 #define AI_ADDRCONFIG	0
218 #endif
219 
220 #ifndef AI_ALL
221 #define AI_ALL	0
222 #endif
223 
224 #ifndef AI_V4MAPPED
225 #define AI_V4MAPPED	0
226 #endif
227 
228 constantFunction (aiAddrconfig, AI_ADDRCONFIG)
229 constantFunction (aiCanonname, AI_CANONNAME)
230 constantFunction (aiAll, AI_ALL)
231 constantFunction (aiV4mapped, AI_V4MAPPED)
232 
233 
234 
235 #if defined SOCK_CLOEXEC && !defined __MSVCRT__
236 /* 0 = unknown, 1 = yes, -1 = no.  */
237 static mst_Boolean have_sock_cloexec;
238 
239 /* Return 0 if the operation failed and an error can be returned
240    by the caller.  */
241 static inline int
check_have_sock_cloexec(int fh,int expected_errno)242 check_have_sock_cloexec (int fh, int expected_errno)
243 {
244   if (have_sock_cloexec == 0 && (fh >= 0 || errno == expected_errno))
245     have_sock_cloexec = (fh >= 0 ? 1 : -1);
246   return (have_sock_cloexec != 0);
247 }
248 #endif
249 
250 static void
socket_set_cloexec(SOCKET fh)251 socket_set_cloexec (SOCKET fh)
252 {
253   if (fh == SOCKET_ERROR)
254     return;
255 
256 #if defined __MSVCRT__
257   /* Do not do FD_CLOEXEC under MinGW.  */
258   SetHandleInformation ((HANDLE) fh, HANDLE_FLAG_INHERIT, 0);
259 #else
260   fcntl (fh, F_SETFD, fcntl (fh, F_GETFD, 0) | FD_CLOEXEC);
261 #endif
262 }
263 
264 static int
mySocket(int domain,int type,int protocol)265 mySocket (int domain, int type, int protocol)
266 {
267   SOCKET fh = SOCKET_ERROR;
268   int fd;
269 
270 #if defined SOCK_CLOEXEC && !defined __MSVCRT__
271   if (have_sock_cloexec >= 0)
272     {
273       fh = socket (domain, type | SOCK_CLOEXEC, protocol);
274       if (!check_have_sock_cloexec (fh, EINVAL))
275 	return -1;
276     }
277 #endif
278   if (fh == SOCKET_ERROR)
279     {
280       fh = socket (domain, type, protocol);
281       socket_set_cloexec (fh);
282     }
283 
284   fd = (fh == SOCKET_ERROR ? -1 : SOCKET_TO_FD (fh));
285   if (fd != SOCKET_ERROR)
286     _gst_register_socket (fd, false);
287   return fd;
288 }
289 
290 
291 /* BSD systems have sa_len, others have not.  Smalltalk will always
292    write sockaddr structs as if they had it.  So for Linux and Winsock
293    we read the second byte (sa_family on BSD systems) and write it in the
294    entire sa_family field. */
295 static inline void
fix_sockaddr(struct sockaddr * sockaddr,socklen_t len)296 fix_sockaddr (struct sockaddr *sockaddr, socklen_t len)
297 {
298 #ifndef HAVE_STRUCT_SOCKADDR_SA_LEN
299   /* Make sure sa_family is a short.  */
300   char verify[sizeof (sockaddr->sa_family) == 2 ? 1 : -1];
301 
302   if (len >= 2)
303     sockaddr->sa_family = ((unsigned char *) sockaddr)[1];
304 #endif
305 }
306 
307 /* Same as connect, but forces the socket to be in non-blocking mode */
308 static int
myConnect(int fd,struct sockaddr * sockaddr,int len)309 myConnect (int fd, struct sockaddr *sockaddr, int len)
310 {
311   SOCKET sock = FD_TO_SOCKET (fd);
312   int rc;
313 
314 #ifdef __MSVCRT__
315   unsigned long iMode = 1;
316   ioctlsocket (sock, FIONBIO, &iMode);
317 
318 #elif defined F_GETFL
319 #ifndef O_NONBLOCK
320 #warning Non-blocking I/O could not be enabled
321 #else
322   int oldflags = fcntl (sock, F_GETFL, NULL);
323   if (!(oldflags & O_NONBLOCK))
324     fcntl (sock, F_SETFL, oldflags | O_NONBLOCK);
325 #endif
326 #endif
327 
328   fix_sockaddr (sockaddr, len);
329   rc = connect (sock, sockaddr, len);
330   if (rc == 0 || is_socket_error (EINPROGRESS) || is_socket_error (EWOULDBLOCK))
331     return 0;
332   else
333     return -1;
334 }
335 
336 static int
myAccept(int fd,struct sockaddr * addr,socklen_t * addrlen)337 myAccept (int fd, struct sockaddr *addr, socklen_t *addrlen)
338 {
339   SOCKET fh = SOCKET_ERROR;
340   int new_fd;
341 
342   /* Parameters to system calls are not guaranteed to generate a SIGSEGV
343      and for this reason we must touch them manually.  */
344   _gst_grey_oop_range (addr, *addrlen);
345 
346 #if defined SOCK_CLOEXEC && defined HAVE_ACCEPT4 && !defined __MSVCRT__
347   if (have_sock_cloexec >= 0)
348     {
349       fh = accept4 (FD_TO_SOCKET (fd), addr, addrlen, SOCK_CLOEXEC);
350       if (!check_have_sock_cloexec (fh, ENOSYS))
351 	return -1;
352     }
353 #endif
354   if (fh == SOCKET_ERROR)
355     {
356       fh = accept (FD_TO_SOCKET (fd), addr, addrlen);
357       socket_set_cloexec (fh);
358     }
359 
360   new_fd = (fh == SOCKET_ERROR ? -1 : SOCKET_TO_FD (fh));
361   if (new_fd != SOCKET_ERROR)
362     _gst_register_socket (new_fd, false);
363   return new_fd;
364 }
365 
366 static int
myBind(int fd,struct sockaddr * addr,socklen_t addrlen)367 myBind (int fd, struct sockaddr *addr, socklen_t addrlen)
368 {
369   fix_sockaddr (addr, addrlen);
370   return bind (FD_TO_SOCKET (fd), addr, addrlen);
371 }
372 
373 static int
myGetpeername(int fd,struct sockaddr * addr,socklen_t * addrlen)374 myGetpeername (int fd, struct sockaddr *addr, socklen_t *addrlen)
375 {
376   /* Parameters to system calls are not guaranteed to generate a SIGSEGV
377      and for this reason we must touch them manually.  */
378   _gst_grey_oop_range (addr, *addrlen);
379 
380   return getpeername (FD_TO_SOCKET (fd), addr, addrlen);
381 }
382 
383 static int
myGetsockname(int fd,struct sockaddr * addr,socklen_t * addrlen)384 myGetsockname (int fd, struct sockaddr *addr, socklen_t *addrlen)
385 {
386   /* Parameters to system calls are not guaranteed to generate a SIGSEGV
387      and for this reason we must touch them manually.  */
388   _gst_grey_oop_range (addr, *addrlen);
389 
390   return getsockname (FD_TO_SOCKET (fd), addr, addrlen);
391 }
392 
393 static int
myGetsockopt(int fd,int level,int optname,char * optval,socklen_t * optlen)394 myGetsockopt (int fd, int level, int optname, char *optval, socklen_t *optlen)
395 {
396   /* Parameters to system calls are not guaranteed to generate a SIGSEGV
397      and for this reason we must touch them manually.  */
398   _gst_grey_oop_range (optval, *optlen);
399 
400   return getsockopt (FD_TO_SOCKET (fd), level, optname, optval, optlen);
401 }
402 
403 static int
myListen(int fd,int backlog)404 myListen (int fd, int backlog)
405 {
406   int r = listen (FD_TO_SOCKET (fd), backlog);
407   if (r != SOCKET_ERROR)
408     _gst_register_socket (fd, true);
409   return r;
410 }
411 
412 static int
myRecvfrom(int fd,char * buf,int len,int flags,struct sockaddr * from,socklen_t * fromlen)413 myRecvfrom (int fd, char *buf, int len, int flags, struct sockaddr *from,
414 	    socklen_t *fromlen)
415 {
416   int frombufsize = *fromlen;
417   int r;
418 
419   /* Parameters to system calls are not guaranteed to generate a SIGSEGV
420      and for this reason we must touch them manually.  */
421   _gst_grey_oop_range (buf, len);
422   _gst_grey_oop_range (from, *fromlen);
423 
424   r = recvfrom (FD_TO_SOCKET (fd), buf, len, flags, from, fromlen);
425 
426   /* Winsock recvfrom() only returns a valid 'from' when the socket is
427      connectionless.  POSIX gives a valid 'from' for all types of sockets.  */
428   if (r != SOCKET_ERROR && frombufsize == *fromlen)
429     (void) myGetpeername (fd, from, fromlen);
430 
431   return r;
432 }
433 
434 static int
mySendto(int fd,const char * buf,int len,int flags,struct sockaddr * to,int tolen)435 mySendto (int fd, const char *buf, int len, int flags,
436 	  struct sockaddr *to, int tolen)
437 {
438   fix_sockaddr (to, tolen);
439   return sendto (FD_TO_SOCKET (fd), buf, len, flags, to, tolen);
440 }
441 
442 static int
mySetsockopt(int fd,int level,int optname,const char * optval,int optlen)443 mySetsockopt (int fd, int level, int optname, const char *optval, int optlen)
444 {
445   return setsockopt (FD_TO_SOCKET (fd), level, optname, optval, optlen);
446 }
447 
448 static int
getSoError(int fd)449 getSoError (int fd)
450 {
451   int error;
452   socklen_t size = sizeof (error);
453   if ((error = _gst_get_fd_error (fd)) != 0)
454     ;
455 
456   else if (myGetsockopt (fd, SOL_SOCKET, SO_ERROR, (char *)&error, &size) == -1)
457     {
458 #if defined _WIN32 && !defined __CYGWIN__
459       error = WSAGetLastError ();
460 #else
461       error = errno;
462 #endif
463     }
464 
465   /* When we get one of these, we don't return an error.  However,
466      the primitive still fails and the file/socket is closed by the
467      Smalltalk code.  */
468   if (error == ESHUTDOWN || error == ECONNRESET
469       || error == ECONNABORTED || error == ENETRESET
470       || error == EPIPE)
471     return 0;
472   else
473     return error;
474 }
475 
476 
477 void
_gst_init_sockets()478 _gst_init_sockets ()
479 {
480 #if defined WIN32 && !defined __CYGWIN__
481   WSADATA wsaData;
482   int iRet;
483   iRet = WSAStartup(MAKEWORD(2,2), &wsaData);
484   if (iRet != 0) {
485     printf("WSAStartup failed (looking for Winsock 2.2): %d\n", iRet);
486     return;
487   }
488 #endif /* _WIN32 */
489 
490   _gst_define_cfunc ("TCPgetaddrinfo", getaddrinfo);
491   _gst_define_cfunc ("TCPfreeaddrinfo", freeaddrinfo);
492   _gst_define_cfunc ("TCPgetHostByAddr", myGetHostByAddr);
493   _gst_define_cfunc ("TCPgetLocalName", myGetHostName);
494   _gst_define_cfunc ("TCPgetAiCanonname", get_aiCanonname);
495   _gst_define_cfunc ("TCPgetAiAddr", get_aiAddr);
496 
497   _gst_define_cfunc ("TCPaccept", myAccept);
498   _gst_define_cfunc ("TCPbind", myBind);
499   _gst_define_cfunc ("TCPconnect", myConnect);
500   _gst_define_cfunc ("TCPgetpeername", myGetpeername);
501   _gst_define_cfunc ("TCPgetsockname", myGetsockname);
502   _gst_define_cfunc ("TCPlisten", myListen);
503   _gst_define_cfunc ("TCPrecvfrom", myRecvfrom);
504   _gst_define_cfunc ("TCPsendto", mySendto);
505   _gst_define_cfunc ("TCPsetsockopt", mySetsockopt);
506   _gst_define_cfunc ("TCPgetsockopt", myGetsockopt);
507   _gst_define_cfunc ("TCPgetSoError", getSoError);
508   _gst_define_cfunc ("TCPsocket", mySocket);
509 
510   _gst_define_cfunc ("TCPpfUnspec", pfUnspec);
511   _gst_define_cfunc ("TCPpfInet", pfInet);
512   _gst_define_cfunc ("TCPpfInet6", pfInet6);
513   _gst_define_cfunc ("TCPpfUnix", pfUnix);
514   _gst_define_cfunc ("TCPafUnspec", afUnspec);
515   _gst_define_cfunc ("TCPafInet", afInet);
516   _gst_define_cfunc ("TCPafInet6", afInet6);
517   _gst_define_cfunc ("TCPafUnix", afUnix);
518   _gst_define_cfunc ("TCPipMulticastTtl", ipMulticastTtl);
519   _gst_define_cfunc ("TCPipMulticastIf", ipMulticastIf);
520   _gst_define_cfunc ("TCPipAddMembership", ipAddMembership);
521   _gst_define_cfunc ("TCPipDropMembership", ipDropMembership);
522   _gst_define_cfunc ("TCPtcpNodelay", tcpNodelay);
523   _gst_define_cfunc ("TCPmsgPeek", msgPeek);
524   _gst_define_cfunc ("TCPmsgOOB", msgOOB);
525   _gst_define_cfunc ("TCPsolSocket", solSocket);
526   _gst_define_cfunc ("TCPsoLinger", soLinger);
527   _gst_define_cfunc ("TCPsoReuseAddr", soReuseAddr);
528   _gst_define_cfunc ("TCPsockStream", sockStream);
529   _gst_define_cfunc ("TCPsockRaw", sockRaw);
530   _gst_define_cfunc ("TCPsockRDM", sockRDM);
531   _gst_define_cfunc ("TCPsockDgram", sockDgram);
532   _gst_define_cfunc ("TCPipprotoIp", ipprotoIp);
533   _gst_define_cfunc ("TCPipprotoTcp", ipprotoTcp);
534   _gst_define_cfunc ("TCPipprotoUdp", ipprotoUdp);
535   _gst_define_cfunc ("TCPipprotoIcmp", ipprotoIcmp);
536   _gst_define_cfunc ("TCPipprotoIcmpv6", ipprotoIcmpv6);
537   _gst_define_cfunc ("TCPaiAddrconfig", aiAddrconfig);
538   _gst_define_cfunc ("TCPaiCanonname", aiCanonname);
539   _gst_define_cfunc ("TCPaiAll", aiAll);
540   _gst_define_cfunc ("TCPaiV4mapped", aiV4mapped);
541 }
542 
543 #else /* !HAVE_SOCKETS */
544 
545 void
_gst_init_sockets()546 _gst_init_sockets ()
547 {
548 }
549 #endif
550