~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to erts/emulator/drivers/common/inet_drv.c

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
/*
2
2
 * %CopyrightBegin%
3
 
 * 
4
 
 * Copyright Ericsson AB 1997-2009. All Rights Reserved.
5
 
 * 
 
3
 *
 
4
 * Copyright Ericsson AB 1997-2011. All Rights Reserved.
 
5
 *
6
6
 * The contents of this file are subject to the Erlang Public License,
7
7
 * Version 1.1, (the "License"); you may not use this file except in
8
8
 * compliance with the License. You should have received a copy of the
9
9
 * Erlang Public License along with this software. If not, it can be
10
10
 * retrieved online at http://www.erlang.org/.
11
 
 * 
 
11
 *
12
12
 * Software distributed under the License is distributed on an "AS IS"
13
13
 * basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
 * the License for the specific language governing rights and limitations
15
15
 * under the License.
16
 
 * 
 
16
 *
17
17
 * %CopyrightEnd%
18
18
 */
19
19
 
41
41
#define STRINGIFY_1(b) IDENTITY(#b)
42
42
#define STRINGIFY(a) STRINGIFY_1(a)
43
43
 
44
 
#ifndef _OSE_
45
44
#ifdef HAVE_UNISTD_H
46
45
#include <unistd.h>
47
46
#endif
48
47
#ifdef HAVE_SYS_UIO_H
49
48
#include <sys/uio.h>
50
49
#endif
51
 
#endif
52
50
 
 
51
#ifdef HAVE_NET_IF_DL_H
 
52
#include <net/if_dl.h>
 
53
#endif
 
54
#ifdef HAVE_IFADDRS_H
 
55
#include <ifaddrs.h>
 
56
#endif
 
57
#ifdef HAVE_NETPACKET_PACKET_H
 
58
#include <netpacket/packet.h>
 
59
#endif
53
60
 
54
61
/* All platforms fail on malloc errors. */
55
62
#define FATAL_MALLOC
57
64
 
58
65
#include "erl_driver.h"
59
66
 
 
67
/* The IS_SOCKET_ERROR macro below is used for portability reasons. While
 
68
   POSIX specifies that errors from socket-related system calls should be
 
69
   indicated with a -1 return value, some users have experienced non-Windows
 
70
   OS kernels that return negative values other than -1. While one can argue
 
71
   that such kernels are technically broken, comparing against values less
 
72
   than 0 covers their out-of-spec return values without imposing incorrect
 
73
   semantics on systems that manage to correctly return -1 for errors, thus
 
74
   increasing Erlang's portability.
 
75
*/
 
76
#ifdef __WIN32__
 
77
#define IS_SOCKET_ERROR(val) ((val) == SOCKET_ERROR)
 
78
#else
 
79
#define IS_SOCKET_ERROR(val) ((val) < 0)
 
80
#endif
 
81
 
60
82
#ifdef __WIN32__
61
83
#define  STRNCASECMP strncasecmp
62
84
 
66
88
#include <winsock2.h>
67
89
#endif
68
90
#include <windows.h>
69
 
 
70
 
#include <Ws2tcpip.h>   /* NEED VC 6.0 !!! */
 
91
#include <Ws2tcpip.h>   /* NEED VC 6.0 or higher */
 
92
 
 
93
/* Visual studio 2008+: NTDDI_VERSION needs to be set for iphlpapi.h
 
94
   to define the right structures. It needs to be set to WINXP (or LONGHORN)
 
95
   for IPV6 to work and it's set lower by default, so we need to change it. */
 
96
#ifdef HAVE_SDKDDKVER_H
 
97
#  include <sdkddkver.h>
 
98
#  ifdef NTDDI_VERSION 
 
99
#    undef NTDDI_VERSION
 
100
#  endif
 
101
#  define NTDDI_VERSION NTDDI_WINXP
 
102
#endif
 
103
 
 
104
#include <iphlpapi.h>
 
105
 
71
106
 
72
107
#undef WANT_NONBLOCKING
73
108
#include "sys.h"
186
221
#include <netdb.h>
187
222
#endif
188
223
 
189
 
#ifndef _OSE_
190
224
#include <sys/socket.h>
191
225
#include <netinet/in.h>
192
 
#else
193
 
/* datatypes and macros from Solaris socket.h */
194
 
struct  linger {
195
 
        int     l_onoff;                /* option on/off */
196
 
        int     l_linger;               /* linger time */
197
 
};
198
 
#define SO_OOBINLINE    0x0100          /* leave received OOB data in line */
199
 
#define SO_LINGER       0x0080          /* linger on close if data present */
200
 
#endif
201
226
 
202
227
#ifdef VXWORKS
203
228
#include <rpc/rpctypes.h>
206
231
#include <rpc/types.h>
207
232
#endif
208
233
 
209
 
#ifndef _OSE_
210
234
#include <netinet/tcp.h>
211
235
#include <arpa/inet.h>
212
 
#endif
213
236
 
214
 
#if (!defined(VXWORKS) && !defined(_OSE_))
 
237
#if (!defined(VXWORKS))
215
238
#include <sys/param.h>
216
239
#ifdef HAVE_ARPA_NAMESER_H
217
240
#include <arpa/nameser.h>
226
249
#include <sys/ioctl.h>
227
250
#endif
228
251
 
229
 
#ifndef _OSE_
230
252
#include <net/if.h>
231
 
#else
232
 
#define IFF_MULTICAST 0x00000800
233
 
#endif
234
 
 
235
 
#ifdef _OSE_
236
 
#include "inet.h"
237
 
#include "ineterr.h"
238
 
#include "ose_inet_drv.h"
239
 
#include "nameser.h" 
240
 
#include "resolv.h"
241
 
#define SET_ASYNC(s) setsockopt((s), SOL_SOCKET, SO_OSEEVENT, (&(s)), sizeof(int))
242
 
 
243
 
extern void select_release(void);
244
 
 
245
 
#endif /* _OSE_ */
246
 
 
247
 
/* Solaris headers, only to be used with SFK */
248
 
#ifdef _OSE_SFK_
249
 
#include <ctype.h>
250
 
#include <string.h>
251
 
#endif
252
253
 
253
254
/* SCTP support -- currently for UNIX platforms only: */
254
255
#undef HAVE_SCTP
255
 
#if (!defined(VXWORKS) && !defined(_OSE_) && !defined(__WIN32__) && defined(HAVE_SCTP_H))
 
256
#if (!defined(VXWORKS) && !defined(__WIN32__) && defined(HAVE_SCTP_H))
256
257
 
257
258
#include <netinet/sctp.h>
258
259
 
315
316
#define DEBUGF(X) printf X
316
317
#endif
317
318
 
318
 
#if !defined(__WIN32__) && !defined(HAVE_STRNCASECMP)
 
319
#if !defined(HAVE_STRNCASECMP)
319
320
#define STRNCASECMP my_strncasecmp
320
321
 
321
322
static int my_strncasecmp(const char *s1, const char *s2, size_t n)
335
336
#define INVALID_SOCKET -1
336
337
#define INVALID_EVENT  -1
337
338
#define SOCKET_ERROR   -1
 
339
 
338
340
#define SOCKET int
339
341
#define HANDLE long int
340
342
#define FD_READ    ERL_DRV_READ
362
364
#define sock_htons(x)               htons((x))
363
365
#define sock_htonl(x)               htonl((x))
364
366
 
365
 
#ifdef _OSE_
366
 
#define sock_accept(s, addr, len)   ose_inet_accept((s), (addr), (len))
367
 
#define sock_send(s,buf,len,flag)   ose_inet_send((s),(buf),(len),(flag))
368
 
#define sock_sendto(s,buf,blen,flag,addr,alen) \
369
 
                ose_inet_sendto((s),(buf),(blen),(flag),(addr),(alen))
370
 
#define sock_sendv(s, vec, size, np, flag) \
371
 
                (*(np) = ose_inet_sendv((s), (SysIOVec*)(vec), (size)))
372
 
#define sock_open(af, type, proto)  ose_inet_socket((af), (type), (proto))
373
 
#define sock_close(s)               ose_inet_close((s))
374
 
#define sock_hostname(buf, len)     ose_gethostname((buf), (len))
375
 
#define sock_getservbyname(name,proto) ose_getservbyname((name), (proto))
376
 
#define sock_getservbyport(port,proto) ose_getservbyport((port), (proto))
377
 
 
378
 
#else
379
367
#define sock_accept(s, addr, len)   accept((s), (addr), (len))
380
368
#define sock_send(s,buf,len,flag)   send((s),(buf),(len),(flag))
381
369
#define sock_sendto(s,buf,blen,flag,addr,alen) \
391
379
#define sock_hostname(buf, len)     gethostname((buf), (len))
392
380
#define sock_getservbyname(name,proto) getservbyname((name), (proto))
393
381
#define sock_getservbyport(port,proto) getservbyport((port), (proto))
394
 
#endif /* _OSE_ */
395
382
 
396
383
#define sock_recv(s,buf,len,flag)   recv((s),(buf),(len),(flag))
397
384
#define sock_recvfrom(s,buf,blen,flag,addr,alen) \
402
389
#define sock_create_event(d)        ((d)->s) /* return file descriptor */
403
390
#define sock_close_event(e)                  /* do nothing */
404
391
 
405
 
#ifdef _OSE_
406
 
#define inet_driver_select(port, e, mode, on) \
407
 
                                    ose_inet_select(port, e, mode, on)
408
 
#else
409
392
#define inet_driver_select(port, e, mode, on) \
410
393
                                    driver_select(port, e, mode | (on?ERL_DRV_USE:0), on)
411
 
#endif /* _OSE_ */
412
394
 
413
395
#define sock_select(d, flags, onoff) do { \
414
396
        (d)->event_mask = (onoff) ? \
501
483
#define INET_REQ_IFGET         22
502
484
#define INET_REQ_IFSET         23
503
485
#define INET_REQ_SUBSCRIBE     24
 
486
#define INET_REQ_GETIFADDRS    25
504
487
/* TCP requests */
505
488
#define TCP_REQ_ACCEPT         40
506
489
#define TCP_REQ_LISTEN         41
666
649
#define IS_BUSY(d) \
667
650
  (((d)->state & INET_F_BUSY) == INET_F_BUSY)
668
651
 
 
652
#define INET_MAX_OPT_BUFFER (64*1024)
 
653
 
669
654
#define INET_DEF_BUFFER     1460        /* default buffer size */
670
655
#define INET_MIN_BUFFER     1           /* internal min buffer */
671
 
#define INET_MAX_BUFFER     (1024*64)   /* internal max buffer */
672
656
 
673
 
/* Note: INET_HIGH_WATERMARK MUST be less than 2*INET_MAX_BUFFER */
674
657
#define INET_HIGH_WATERMARK (1024*8) /* 8k pending high => busy  */
675
 
/* Note: INET_LOW_WATERMARK MUST be less than INET_MAX_BUFFER and
676
 
** less than INET_HIGH_WATERMARK
677
 
*/
678
658
#define INET_LOW_WATERMARK  (1024*4) /* 4k pending => allow more */
679
659
 
680
660
#define INET_INFINITY  0xffffffff  /* infinity value */
1085
1065
};
1086
1066
 
1087
1067
/* XXX: is this a driver interface function ??? */
1088
 
extern void erl_exit(int n, char*, _DOTS_);
 
1068
void erl_exit(int n, char*, ...);
1089
1069
 
1090
1070
/*
1091
1071
 * Malloc wrapper,
1205
1185
    /* For AssocID, 4 bytes should be enough -- checked by "init": */
1206
1186
#   define GET_ASSOC_ID         get_int32
1207
1187
#   define ASSOC_ID_LEN         4
1208
 
#   define LOAD_ASSOC_ID        LOAD_INT
1209
 
#   define LOAD_ASSOC_ID_CNT    LOAD_INT_CNT
 
1188
#   define LOAD_ASSOC_ID        LOAD_UINT
 
1189
#   define LOAD_ASSOC_ID_CNT    LOAD_UINT_CNT
1210
1190
#   define SCTP_ANC_BUFF_SIZE   INET_DEF_BUFFER/2 /* XXX: not very good... */
1211
1191
#endif
1212
1192
 
1285
1265
        LOAD_ATOM((spec), (i), (flag) ? am_true : am_false);
1286
1266
#endif /* HAVE_SCTP */
1287
1267
 
 
1268
/* Assume a cache line size of 64 bytes */
 
1269
#define INET_DRV_CACHE_LINE_SIZE ((ErlDrvUInt) 64)
 
1270
#define INET_DRV_CACHE_LINE_MASK (INET_DRV_CACHE_LINE_SIZE - 1)
 
1271
 
1288
1272
/*
1289
1273
** Binary Buffer Managment
1290
1274
** We keep a stack of usable buffers 
1291
1275
*/
1292
 
#define BUFFER_STACK_SIZE 16
1293
 
 
1294
 
static erts_smp_spinlock_t inet_buffer_stack_lock;
1295
 
static ErlDrvBinary* buffer_stack[BUFFER_STACK_SIZE];
1296
 
static int buffer_stack_pos = 0;
1297
 
 
1298
 
 
1299
 
/*
1300
 
 * XXX
1301
 
 * The erts_smp_spin_* functions should not be used by drivers (but this
1302
 
 * driver is special). Replace when driver locking api has been implemented.
1303
 
 * /rickard
1304
 
 */
1305
 
#define BUFSTK_LOCK     erts_smp_spin_lock(&inet_buffer_stack_lock);
1306
 
#define BUFSTK_UNLOCK   erts_smp_spin_unlock(&inet_buffer_stack_lock);
1307
 
 
1308
 
#ifdef DEBUG
1309
 
static int tot_buf_allocated = 0;  /* memory in use for i_buf */
1310
 
static int tot_buf_stacked = 0;   /* memory on stack */
1311
 
static int max_buf_allocated = 0; /* max allocated */
1312
 
 
1313
 
#define COUNT_BUF_ALLOC(sz) do { \
1314
 
  BUFSTK_LOCK; \
1315
 
  tot_buf_allocated += (sz); \
1316
 
  if (tot_buf_allocated > max_buf_allocated) \
1317
 
    max_buf_allocated = tot_buf_allocated; \
1318
 
  BUFSTK_UNLOCK; \
1319
 
} while(0)
1320
 
 
1321
 
#define COUNT_BUF_FREE(sz) do { \
1322
 
 BUFSTK_LOCK; \
1323
 
 tot_buf_allocated -= (sz); \
1324
 
 BUFSTK_UNLOCK; \
1325
 
 } while(0)
1326
 
 
1327
 
#define COUNT_BUF_STACK(sz) do { \
1328
 
 BUFSTK_LOCK; \
1329
 
 tot_buf_stacked += (sz); \
1330
 
 BUFSTK_UNLOCK; \
1331
 
 } while(0)
1332
 
 
1333
 
#else
1334
 
 
1335
 
#define COUNT_BUF_ALLOC(sz)
1336
 
#define COUNT_BUF_FREE(sz)
1337
 
#define COUNT_BUF_STACK(sz)
1338
 
 
1339
 
#endif
 
1276
#define BUFFER_STACK_SIZE 14
 
1277
#define BUFFER_STACK_MAX_MEM_SIZE (1024*1024)
 
1278
 
 
1279
ErlDrvTSDKey buffer_stack_key;
 
1280
 
 
1281
typedef struct {
 
1282
    int mem_size;
 
1283
    int pos;
 
1284
    ErlDrvBinary* stk[BUFFER_STACK_SIZE];
 
1285
} InetDrvBufStkBase;
 
1286
 
 
1287
typedef struct {
 
1288
    InetDrvBufStkBase buf;
 
1289
    char align[(((sizeof(InetDrvBufStkBase) - 1) / INET_DRV_CACHE_LINE_SIZE) + 1)
 
1290
               * INET_DRV_CACHE_LINE_SIZE];
 
1291
} InetDrvBufStk;
 
1292
 
 
1293
static InetDrvBufStk *get_bufstk(void)
 
1294
{
 
1295
    InetDrvBufStk *bs = erl_drv_tsd_get(buffer_stack_key);
 
1296
    if (bs)
 
1297
        return bs;
 
1298
    bs = driver_alloc(sizeof(InetDrvBufStk)
 
1299
                      + INET_DRV_CACHE_LINE_SIZE - 1);
 
1300
    if (!bs)
 
1301
        return NULL;
 
1302
    if ((((ErlDrvUInt) bs) & INET_DRV_CACHE_LINE_MASK) != 0)
 
1303
        bs = ((InetDrvBufStk *)
 
1304
              ((((ErlDrvUInt) bs) & ~INET_DRV_CACHE_LINE_MASK)
 
1305
               + INET_DRV_CACHE_LINE_SIZE));
 
1306
    erl_drv_tsd_set(buffer_stack_key, bs);
 
1307
    bs->buf.pos = 0;
 
1308
    bs->buf.mem_size = 0;
 
1309
 
 
1310
    ASSERT(bs == erl_drv_tsd_get(buffer_stack_key));
 
1311
 
 
1312
    return bs;
 
1313
}
1340
1314
 
1341
1315
static ErlDrvBinary* alloc_buffer(long minsz)
1342
1316
{
1343
 
    ErlDrvBinary* buf = NULL;
1344
 
 
1345
 
    BUFSTK_LOCK;
1346
 
 
1347
 
    DEBUGF(("alloc_buffer: sz = %ld, tot = %d, max = %d\r\n", 
1348
 
            minsz, tot_buf_allocated, max_buf_allocated));
1349
 
 
1350
 
    if (buffer_stack_pos > 0) {
1351
 
        int origsz;
1352
 
 
1353
 
        buf = buffer_stack[--buffer_stack_pos];
1354
 
        origsz = buf->orig_size;
1355
 
        BUFSTK_UNLOCK;
1356
 
        COUNT_BUF_STACK(-origsz);
1357
 
        if (origsz < minsz) {
1358
 
            if ((buf = driver_realloc_binary(buf, minsz)) == NULL)
1359
 
                return NULL;
1360
 
            COUNT_BUF_ALLOC(buf->orig_size - origsz);
1361
 
        }
1362
 
    }
1363
 
    else {
1364
 
        BUFSTK_UNLOCK;
1365
 
        if ((buf = driver_alloc_binary(minsz)) == NULL)
1366
 
            return NULL;
1367
 
        COUNT_BUF_ALLOC(buf->orig_size);
1368
 
    }
1369
 
    return buf;
 
1317
    InetDrvBufStk *bs = get_bufstk();
 
1318
 
 
1319
    DEBUGF(("alloc_buffer: %ld\r\n", minsz));
 
1320
 
 
1321
    if (bs && bs->buf.pos > 0) {
 
1322
        long size;
 
1323
        ErlDrvBinary* buf = bs->buf.stk[--bs->buf.pos];
 
1324
        size = buf->orig_size;
 
1325
        bs->buf.mem_size -= size;
 
1326
        ASSERT(0 <= bs->buf.mem_size
 
1327
               && bs->buf.mem_size <= BUFFER_STACK_MAX_MEM_SIZE);
 
1328
        if (size >= minsz)
 
1329
            return buf;
 
1330
 
 
1331
        driver_free_binary(buf);
 
1332
    }
 
1333
 
 
1334
    ASSERT(!bs || bs->buf.pos != 0 || bs->buf.mem_size == 0);
 
1335
 
 
1336
    return driver_alloc_binary(minsz);
1370
1337
}
1371
1338
 
1372
 
/*
1373
 
** Max buffer memory "cached" BUFFER_STACK_SIZE * INET_MAX_BUFFER
1374
 
** (16 * 64k ~ 1M)
1375
 
*/
1376
1339
/*#define CHECK_DOUBLE_RELEASE 1*/
 
1340
#ifdef CHECK_DOUBLE_RELEASE
 
1341
static void
 
1342
check_double_release(InetDrvBufStk *bs, ErlDrvBinary* buf)
 
1343
{
 
1344
#ifdef __GNUC__
 
1345
#warning CHECK_DOUBLE_RELEASE is enabled, this is a custom build emulator
 
1346
#endif
 
1347
    int i;
 
1348
    for (i = 0; i < bs->buf.pos; ++i) {
 
1349
        if (bs->buf.stk[i] == buf) {
 
1350
            erl_exit(ERTS_ABORT_EXIT,
 
1351
                     "Multiple buffer release in inet_drv, this "
 
1352
                     "is a bug, save the core and send it to "
 
1353
                     "support@erlang.ericsson.se!");
 
1354
        }
 
1355
    }
 
1356
}
 
1357
#endif
 
1358
 
1377
1359
static void release_buffer(ErlDrvBinary* buf)
1378
1360
{
 
1361
    InetDrvBufStk *bs;
 
1362
    long size;
 
1363
 
1379
1364
    DEBUGF(("release_buffer: %ld\r\n", (buf==NULL) ? 0 : buf->orig_size));
1380
 
    if (buf == NULL)
 
1365
 
 
1366
    if (!buf)
1381
1367
        return;
1382
 
    BUFSTK_LOCK;
1383
 
    if ((buf->orig_size > INET_MAX_BUFFER) || 
1384
 
        (buffer_stack_pos >= BUFFER_STACK_SIZE)) {
1385
 
        BUFSTK_UNLOCK;
1386
 
        COUNT_BUF_FREE(buf->orig_size);
 
1368
 
 
1369
    size = buf->orig_size;
 
1370
 
 
1371
    if (size > BUFFER_STACK_MAX_MEM_SIZE)
 
1372
        goto free_binary;
 
1373
 
 
1374
    bs = get_bufstk();
 
1375
    if (!bs
 
1376
        || (bs->buf.mem_size + size > BUFFER_STACK_MAX_MEM_SIZE)
 
1377
        || (bs->buf.pos >= BUFFER_STACK_SIZE)) {
 
1378
    free_binary:
1387
1379
        driver_free_binary(buf);
1388
1380
    }
1389
1381
    else {
1390
1382
#ifdef CHECK_DOUBLE_RELEASE
1391
 
#ifdef __GNUC__
1392
 
#warning CHECK_DOUBLE_RELEASE is enabled, this is a custom build emulator
1393
 
#endif
1394
 
        int i;
1395
 
        for (i = 0; i < buffer_stack_pos; ++i) {
1396
 
            if (buffer_stack[i] == buf) {
1397
 
                erl_exit(1,"Multiple buffer release in inet_drv, this is a "
1398
 
                         "bug, save the core and send it to "
1399
 
                         "support@erlang.ericsson.se!");
1400
 
            }
1401
 
        }
1402
 
#endif
1403
 
        buffer_stack[buffer_stack_pos++] = buf;
1404
 
        BUFSTK_UNLOCK;
1405
 
        COUNT_BUF_STACK(buf->orig_size);
 
1383
        check_double_release(bs, buf);
 
1384
#endif
 
1385
        ASSERT(bs->buf.pos != 0 || bs->buf.mem_size == 0);
 
1386
 
 
1387
        bs->buf.mem_size += size;
 
1388
        bs->buf.stk[bs->buf.pos++] = buf;
 
1389
 
 
1390
        ASSERT(0 <= bs->buf.mem_size
 
1391
               && bs->buf.mem_size <= BUFFER_STACK_MAX_MEM_SIZE);
1406
1392
    }
1407
1393
}
1408
1394
 
1409
1395
static ErlDrvBinary* realloc_buffer(ErlDrvBinary* buf, long newsz)
1410
1396
{
1411
 
    ErlDrvBinary* bin;
1412
 
#ifdef DEBUG
1413
 
    long orig_size =  buf->orig_size;
1414
 
#endif
1415
 
 
1416
 
    if ((bin = driver_realloc_binary(buf,newsz)) != NULL) {
1417
 
        COUNT_BUF_ALLOC(newsz - orig_size);
1418
 
        ;
1419
 
    }
1420
 
    return bin;
 
1397
    return driver_realloc_binary(buf, newsz);
1421
1398
}
1422
1399
 
1423
1400
/* use a TRICK, access the refc field to see if any one else has
1431
1408
    if (buf != NULL) {
1432
1409
        if (driver_binary_get_refc(buf) == 1)
1433
1410
            release_buffer(buf);
1434
 
        else {
1435
 
            COUNT_BUF_FREE(buf->orig_size);
 
1411
        else
1436
1412
            driver_free_binary(buf);
1437
 
        }
1438
1413
    }
1439
1414
}
1440
1415
 
2208
2183
  ErlDrvTermData spec[19];
2209
2184
 
2210
2185
  if (desc->inet.active == INET_PASSIVE) {
2211
 
    /* {inet_async,S,Ref,{error,{http_error,Line}}} */
 
2186
    /* {inet_async,S,Ref,{ok,{http_error,Line}}} */
2212
2187
    int req;
2213
2188
    int aid;
2214
2189
    ErlDrvTermData caller;
2218
2193
    i = LOAD_ATOM(spec, i,  am_inet_async);
2219
2194
    i = LOAD_PORT(spec, i,  desc->inet.dport);
2220
2195
    i = LOAD_INT(spec, i,   aid);
2221
 
    i = LOAD_ATOM(spec, i,  am_error);
 
2196
    i = LOAD_ATOM(spec, i,  am_ok);
2222
2197
    i = LOAD_ATOM(spec, i,  am_http_error);
2223
2198
    i = http_load_string(desc, spec, i, buf, len);
2224
2199
    i = LOAD_TUPLE(spec, i, 2);
3438
3413
    if (!sock_init())
3439
3414
        goto error;
3440
3415
 
3441
 
    buffer_stack_pos = 0;
3442
 
 
3443
 
    erts_smp_spinlock_init(&inet_buffer_stack_lock, "inet_buffer_stack_lock");
 
3416
    if (0 != erl_drv_tsd_key_create("inet_buffer_stack_key", &buffer_stack_key))
 
3417
        goto error;
3444
3418
 
3445
3419
    ASSERT(sizeof(struct in_addr) == 4);
3446
3420
#   if defined(HAVE_IN6) && defined(AF_INET6)
3447
3421
    ASSERT(sizeof(struct in6_addr) == 16);
3448
3422
#   endif
3449
3423
 
3450
 
#ifdef DEBUG
3451
 
    tot_buf_allocated = 0;
3452
 
    max_buf_allocated = 0;
3453
 
    tot_buf_stacked = 0;
3454
 
#endif
3455
3424
    INIT_ATOM(ok);
3456
3425
    INIT_ATOM(tcp);
3457
3426
    INIT_ATOM(udp);
3480
3449
    INIT_ATOM(scheme);
3481
3450
 
3482
3451
    /* add TCP, UDP and SCTP drivers */
3483
 
#ifdef _OSE_
3484
 
    add_ose_tcp_drv_entry(&tcp_inet_driver_entry);
3485
 
    add_ose_udp_drv_entry(&udp_inet_driver_entry);
3486
 
#else
3487
3452
    add_driver_entry(&tcp_inet_driver_entry);
3488
3453
    add_driver_entry(&udp_inet_driver_entry);
3489
 
#  ifdef HAVE_SCTP
 
3454
#ifdef HAVE_SCTP
3490
3455
    /* Check the size of SCTP AssocID -- currently both this driver and the
3491
3456
       Erlang part require 32 bit: */
3492
3457
    ASSERT(sizeof(sctp_assoc_t)==ASSOC_ID_LEN);
3501
3466
            add_driver_entry(&sctp_inet_driver_entry);
3502
3467
        }
3503
3468
    }
3504
 
#  endif
3505
 
#endif /* _OSE_ */
 
3469
#endif
 
3470
 
3506
3471
    /* remove the dummy inet driver */
3507
3472
    remove_driver_entry(&inet_driver_entry);
3508
3473
    return 0;
3744
3709
    unsigned int sz = sizeof(name);
3745
3710
 
3746
3711
    /* check that it is a socket and that the socket is bound */
3747
 
    if (sock_name(s, (struct sockaddr*) &name, &sz) == SOCKET_ERROR)
 
3712
    if (IS_SOCKET_ERROR(sock_name(s, (struct sockaddr*) &name, &sz)))
3748
3713
        return ctl_error(sock_errno(), rbuf, rsize);
3749
3714
    desc->s = s;
3750
3715
    if ((desc->event = sock_create_event(desc)) == INVALID_EVENT)
3756
3721
    desc->state = INET_STATE_BOUND; /* assume bound */
3757
3722
    if (type == SOCK_STREAM) { /* check if connected */
3758
3723
        sz = sizeof(name);
3759
 
        if (sock_peer(s, (struct sockaddr*) &name, &sz) != SOCKET_ERROR)
 
3724
        if (!IS_SOCKET_ERROR(sock_peer(s, (struct sockaddr*) &name, &sz)))
3760
3725
            desc->state = INET_STATE_CONNECTED;
3761
3726
    }
3762
3727
 
3862
3827
static char* sockaddr_to_buf(struct sockaddr* addr, char* ptr, char* end)
3863
3828
{
3864
3829
    if (addr->sa_family == AF_INET || addr->sa_family == 0) {
3865
 
        struct in_addr a;
 
3830
        struct in_addr *p = &(((struct sockaddr_in*) addr)->sin_addr);
 
3831
        buf_check(ptr, end, 1 + sizeof(struct in_addr));
 
3832
        *ptr = INET_AF_INET;
 
3833
        sys_memcpy(ptr+1, (char*)p, sizeof(struct in_addr));
 
3834
        return ptr + 1 + sizeof(struct in_addr);
 
3835
    }
 
3836
#if defined(HAVE_IN6) && defined(AF_INET6)
 
3837
    else if (addr->sa_family == AF_INET6) {
 
3838
        struct in6_addr *p = &(((struct sockaddr_in6*) addr)->sin6_addr);
 
3839
        buf_check(ptr, end, 1 + sizeof(struct in6_addr));
 
3840
        *ptr = INET_AF_INET6;
 
3841
        sys_memcpy(ptr+1, (char*)p, sizeof(struct in6_addr));
 
3842
        return ptr + 1 + sizeof(struct in6_addr);
 
3843
    }
 
3844
#endif
 
3845
#if defined(AF_LINK)
 
3846
    else if (addr->sa_family == AF_LINK) {
 
3847
        struct sockaddr_dl *sdl_p = (struct sockaddr_dl*) addr;
 
3848
        buf_check(ptr, end, 2 + sdl_p->sdl_alen);
 
3849
        put_int16(sdl_p->sdl_alen, ptr); ptr += 2;
 
3850
        sys_memcpy(ptr, sdl_p->sdl_data + sdl_p->sdl_nlen, sdl_p->sdl_alen);
 
3851
        return ptr + sdl_p->sdl_alen;
 
3852
    }
 
3853
#endif
 
3854
#if defined(AF_PACKET) && defined(HAVE_NETPACKET_PACKET_H)
 
3855
    else if(addr->sa_family == AF_PACKET) {
 
3856
        struct sockaddr_ll *sll_p = (struct sockaddr_ll*) addr;
 
3857
        buf_check(ptr, end, 2 + sll_p->sll_halen);
 
3858
        put_int16(sll_p->sll_halen, ptr); ptr += 2;
 
3859
        sys_memcpy(ptr, sll_p->sll_addr, sll_p->sll_halen);
 
3860
        return ptr + sll_p->sll_halen;
 
3861
    }
 
3862
#endif
 
3863
    return ptr;
 
3864
 error:
 
3865
    return NULL;
 
3866
}
 
3867
 
 
3868
static char* buf_to_sockaddr(char* ptr, char* end, struct sockaddr* addr)
 
3869
{
 
3870
    buf_check(ptr,end,1);
 
3871
    switch (*ptr++) {
 
3872
    case INET_AF_INET: {
 
3873
        struct in_addr *p = &((struct sockaddr_in*)addr)->sin_addr;
3866
3874
        buf_check(ptr,end,sizeof(struct in_addr));
3867
 
        a = ((struct sockaddr_in*) addr)->sin_addr;
3868
 
        sys_memcpy(ptr, (char*)&a, sizeof(struct in_addr));
 
3875
        sys_memcpy((char*) p, ptr, sizeof(struct in_addr));
 
3876
        addr->sa_family = AF_INET;
3869
3877
        return ptr + sizeof(struct in_addr);
3870
3878
    }
3871
 
#if defined(HAVE_IN6) && defined(AF_INET6)
3872
 
    else if (addr->sa_family == AF_INET6) {
3873
 
        struct in6_addr a;
 
3879
    case INET_AF_INET6: {
 
3880
        struct in6_addr *p = &((struct sockaddr_in6*)addr)->sin6_addr;
3874
3881
        buf_check(ptr,end,sizeof(struct in6_addr));
3875
 
        a = ((struct sockaddr_in6*) addr)->sin6_addr;
3876
 
        sys_memcpy(ptr, (char*)&a, sizeof(struct in6_addr));
 
3882
        sys_memcpy((char*) p, ptr, sizeof(struct in6_addr));
 
3883
        addr->sa_family = AF_INET6;
3877
3884
        return ptr + sizeof(struct in6_addr);
3878
3885
    }
 
3886
    }
 
3887
 error:
 
3888
    return NULL;
 
3889
}
 
3890
 
 
3891
 
 
3892
#if defined (IFF_POINTOPOINT)
 
3893
#define IFGET_FLAGS(cflags) IFGET_FLAGS_P2P(cflags, IFF_POINTOPOINT)
 
3894
#elif defined IFF_POINTTOPOINT
 
3895
#define IFGET_FLAGS(cflags) IFGET_FLAGS_P2P(cflags, IFF_POINTTOPOINT)
3879
3896
#endif
3880
 
 error:
3881
 
    return NULL;
3882
 
 
3883
 
}
3884
 
 
3885
 
static char* buf_to_sockaddr(char* ptr, char* end, struct sockaddr* addr)
3886
 
{
3887
 
    buf_check(ptr,end,sizeof(struct in_addr));
3888
 
    sys_memcpy((char*) &((struct sockaddr_in*)addr)->sin_addr, ptr,
3889
 
               sizeof(struct in_addr));
3890
 
    addr->sa_family = AF_INET;
3891
 
    return ptr +  sizeof(struct in_addr);
3892
 
 
3893
 
 error:
3894
 
    return NULL;
3895
 
}
3896
 
 
3897
 
 
 
3897
 
 
3898
#define IFGET_FLAGS_P2P(cflags, iff_ptp)                                \
 
3899
    ((((cflags) & IFF_UP) ? INET_IFF_UP : 0) |                          \
 
3900
     (((cflags) & IFF_BROADCAST) ? INET_IFF_BROADCAST : 0) |            \
 
3901
     (((cflags) & IFF_LOOPBACK) ? INET_IFF_LOOPBACK : 0) |              \
 
3902
     (((cflags) & iff_ptp) ? INET_IFF_POINTTOPOINT : 0) |               \
 
3903
     (((cflags) & IFF_UP) ? INET_IFF_RUNNING : 0) |  /* emulate running ? */ \
 
3904
     (((cflags) & IFF_MULTICAST) ? INET_IFF_MULTICAST : 0))
3898
3905
 
3899
3906
#if defined(__WIN32__) && defined(SIO_GET_INTERFACE_LIST)
3900
3907
 
3932
3939
    return ctl_reply(INET_REP_OK, sbuf, sptr - sbuf, rbuf, rsize);
3933
3940
}
3934
3941
 
3935
 
 
3936
3942
/* input is an ip-address in string format i.e A.B.C.D 
3937
3943
** scan the INTERFACE_LIST to get the options 
3938
3944
*/
3949
3955
    INTERFACE_INFO* ifp;
3950
3956
    long namaddr;
3951
3957
 
3952
 
    if ((len == 0) || ((namlen = buf[0]) > len))
 
3958
    if ((len == 0) || ((namlen = get_int8(buf)) > len))
3953
3959
        goto error;
3954
3960
    if (parse_addr(buf+1, namlen, &namaddr) < 0)
3955
3961
        goto error;
4018
4024
            break;
4019
4025
 
4020
4026
        case INET_IFOPT_FLAGS: {
4021
 
            long eflags = 0;
4022
4027
            int flags = ifp->iiFlags;
4023
4028
            /* just enumerate the interfaces (no names) */
4024
4029
 
4025
 
            /* translate flags */
4026
 
            if (flags & IFF_UP)
4027
 
                eflags |= INET_IFF_UP;
4028
 
            if (flags & IFF_BROADCAST)
4029
 
                eflags |= INET_IFF_BROADCAST;
4030
 
            if (flags & IFF_LOOPBACK)
4031
 
                eflags |= INET_IFF_LOOPBACK;
4032
 
            if (flags & IFF_POINTTOPOINT)
4033
 
                eflags |= INET_IFF_POINTTOPOINT;
4034
 
            if (flags & IFF_UP) /* emulate runnign ? */
4035
 
                eflags |= INET_IFF_RUNNING;
4036
 
            if (flags & IFF_MULTICAST)
4037
 
                eflags |= INET_IFF_MULTICAST;
4038
 
 
4039
4030
            buf_check(sptr, s_end, 5);
4040
4031
            *sptr++ = INET_IFOPT_FLAGS;
4041
 
            put_int32(eflags, sptr);
 
4032
            put_int32(IFGET_FLAGS(flags), sptr);
4042
4033
            sptr += 4;
4043
4034
            break;
4044
4035
        }
4059
4050
    return ctl_reply(INET_REP_OK, NULL, 0, rbuf, rsize);
4060
4051
}
4061
4052
 
4062
 
 
4063
4053
#elif defined(SIOCGIFCONF) && defined(SIOCSIFFLAGS)
4064
4054
/* cygwin has SIOCGIFCONF but not SIOCSIFFLAGS (Nov 2002) */
4065
4055
 
4070
4060
#define SIZEA(p) (sizeof (p))
4071
4061
#endif
4072
4062
 
4073
 
 
4074
 
static int inet_ctl_getiflist(inet_descriptor* desc, char** rbuf, int rsize)
4075
 
{
4076
 
    struct ifconf ifc;
4077
 
    struct ifreq *ifr;
4078
 
    char *buf;
4079
 
    int buflen, ifc_len, i;
4080
 
    char *sbuf, *sp;
4081
 
    
4082
 
    /* Courtesy of Per Bergqvist and W. Richard Stevens */
4083
 
    
4084
 
    ifc_len = 0;
4085
 
    buflen = 100 * sizeof(struct ifreq);
4086
 
    buf = ALLOC(buflen);
 
4063
static int get_ifconf(SOCKET s, struct ifconf *ifcp) {
 
4064
    int ifc_len = 0;
 
4065
    int buflen = 100 * sizeof(struct ifreq);
 
4066
    char *buf = ALLOC(buflen);
4087
4067
 
4088
4068
    for (;;) {
4089
 
        ifc.ifc_len = buflen;
4090
 
        ifc.ifc_buf = buf;
4091
 
        if (ioctl(desc->s, SIOCGIFCONF, (char *)&ifc) < 0) {
 
4069
        ifcp->ifc_len = buflen;
 
4070
        ifcp->ifc_buf = buf;
 
4071
        if (ioctl(s, SIOCGIFCONF, (char *)ifcp) < 0) {
4092
4072
            int res = sock_errno();
4093
4073
            if (res != EINVAL || ifc_len) {
4094
4074
                FREE(buf);
4095
 
                return ctl_error(res, rbuf, rsize);
 
4075
                return -1;
4096
4076
            }
4097
4077
        } else {
4098
 
            if (ifc.ifc_len == ifc_len) break; /* buf large enough */
4099
 
            ifc_len = ifc.ifc_len;
 
4078
            if (ifcp->ifc_len == ifc_len) break; /* buf large enough */
 
4079
            ifc_len = ifcp->ifc_len;
4100
4080
        }
4101
4081
        buflen += 10 * sizeof(struct ifreq);
4102
4082
        buf = (char *)REALLOC(buf, buflen);
4103
4083
    }
4104
 
    
4105
 
    sp = sbuf = ALLOC(ifc_len+1);
 
4084
    return 0;
 
4085
}
 
4086
 
 
4087
static void free_ifconf(struct ifconf *ifcp) {
 
4088
    FREE(ifcp->ifc_buf);
 
4089
}
 
4090
 
 
4091
static int inet_ctl_getiflist(inet_descriptor* desc, char** rbuf, int rsize)
 
4092
{
 
4093
    struct ifconf ifc;
 
4094
    struct ifreq *ifrp;
 
4095
    char *sbuf, *sp;
 
4096
    int i;
 
4097
 
 
4098
    /* Courtesy of Per Bergqvist and W. Richard Stevens */
 
4099
 
 
4100
    if (get_ifconf(desc->s, &ifc) < 0) {
 
4101
        return ctl_error(sock_errno(), rbuf, rsize);
 
4102
    }
 
4103
 
 
4104
    sp = sbuf = ALLOC(ifc.ifc_len+1);
4106
4105
    *sp++ = INET_REP_OK;
4107
4106
    i = 0;
4108
4107
    for (;;) {
4109
4108
        int n;
4110
 
        
4111
 
        ifr = (struct ifreq *) VOIDP(buf + i);
4112
 
        n = sizeof(ifr->ifr_name) + SIZEA(ifr->ifr_addr);
4113
 
        if (n < sizeof(*ifr)) n = sizeof(*ifr);
4114
 
        if (i+n > ifc_len) break;
 
4109
 
 
4110
        ifrp = (struct ifreq *) VOIDP(ifc.ifc_buf + i);
 
4111
        n = sizeof(ifrp->ifr_name) + SIZEA(ifrp->ifr_addr);
 
4112
        if (n < sizeof(*ifrp)) n = sizeof(*ifrp);
 
4113
        if (i+n > ifc.ifc_len) break;
4115
4114
        i += n;
4116
 
        
4117
 
        switch (ifr->ifr_addr.sa_family) {
 
4115
 
 
4116
        switch (ifrp->ifr_addr.sa_family) {
4118
4117
#if defined(HAVE_IN6) && defined(AF_INET6)
4119
4118
        case AF_INET6:
4120
4119
#endif
4121
4120
        case AF_INET:
4122
 
            ASSERT(sp+IFNAMSIZ+1 < sbuf+buflen+1)
4123
 
            strncpy(sp, ifr->ifr_name, IFNAMSIZ);
 
4121
            ASSERT(sp+IFNAMSIZ+1 < sbuf+ifc.ifc_len+1)
 
4122
            strncpy(sp, ifrp->ifr_name, IFNAMSIZ);
4124
4123
            sp[IFNAMSIZ] = '\0';
4125
4124
            sp += strlen(sp), ++sp;
4126
4125
        }
4127
 
        
4128
 
        if (i >= ifc_len) break;
 
4126
 
 
4127
        if (i >= ifc.ifc_len) break;
4129
4128
    }
4130
 
    FREE(buf);
 
4129
    free_ifconf(&ifc);
4131
4130
    *rbuf = sbuf;
4132
4131
    return sp - sbuf;
4133
4132
}
4134
4133
 
4135
 
 
 
4134
/* FIXME: temporary hack */
 
4135
#ifndef IFHWADDRLEN
 
4136
#define IFHWADDRLEN 6
 
4137
#endif
4136
4138
 
4137
4139
static int inet_ctl_ifget(inet_descriptor* desc, char* buf, int len,
4138
4140
                          char** rbuf, int rsize)
4143
4145
    struct ifreq ifreq;
4144
4146
    int namlen;
4145
4147
 
4146
 
    if ((len == 0) || ((namlen = buf[0]) > len))
 
4148
    if ((len == 0) || ((namlen = get_int8(buf)) > len))
4147
4149
        goto error;
4148
4150
    sys_memset(ifreq.ifr_name, '\0', IFNAMSIZ);
4149
4151
    sys_memcpy(ifreq.ifr_name, buf+1, 
4150
 
               (namlen > IFNAMSIZ) ? IFNAMSIZ : namlen);
 
4152
               (namlen >= IFNAMSIZ) ? IFNAMSIZ-1 : namlen);
4151
4153
    buf += (namlen+1);
4152
4154
    len -= (namlen+1);
4153
4155
    sptr = sbuf;
4167
4169
#ifdef SIOCGIFHWADDR
4168
4170
            if (ioctl(desc->s, SIOCGIFHWADDR, (char *)&ifreq) < 0)
4169
4171
                break;
4170
 
            buf_check(sptr, s_end, 1+IFHWADDRLEN);
 
4172
            buf_check(sptr, s_end, 1+2+IFHWADDRLEN);
4171
4173
            *sptr++ = INET_IFOPT_HWADDR;
 
4174
            put_int16(IFHWADDRLEN, sptr); sptr += 2;
4172
4175
            /* raw memcpy (fix include autoconf later) */
4173
4176
            sys_memcpy(sptr, (char*)(&ifreq.ifr_hwaddr.sa_data), IFHWADDRLEN);
4174
4177
            sptr += IFHWADDRLEN;
 
4178
#elif defined(SIOCGENADDR)
 
4179
            if (ioctl(desc->s, SIOCGENADDR, (char *)&ifreq) < 0)
 
4180
                break;
 
4181
            buf_check(sptr, s_end, 1+2+sizeof(ifreq.ifr_enaddr));
 
4182
            *sptr++ = INET_IFOPT_HWADDR;
 
4183
            put_int16(sizeof(ifreq.ifr_enaddr), sptr); sptr += 2;
 
4184
            /* raw memcpy (fix include autoconf later) */
 
4185
            sys_memcpy(sptr, (char*)(&ifreq.ifr_enaddr),
 
4186
                       sizeof(ifreq.ifr_enaddr));
 
4187
            sptr += sizeof(ifreq.ifr_enaddr);
 
4188
#elif defined(HAVE_GETIFADDRS) && defined(AF_LINK)
 
4189
            struct ifaddrs *ifa, *ifp;
 
4190
            struct sockaddr_dl *sdlp;
 
4191
            int found = 0;
 
4192
 
 
4193
            if (getifaddrs(&ifa) == -1)
 
4194
                goto error;
 
4195
 
 
4196
            for (ifp = ifa; ifp; ifp = ifp->ifa_next) {
 
4197
                if ((ifp->ifa_addr->sa_family == AF_LINK) &&
 
4198
                    (sys_strcmp(ifp->ifa_name, ifreq.ifr_name) == 0)) {
 
4199
                    found = 1;
 
4200
                    break;
 
4201
                }
 
4202
            }
 
4203
 
 
4204
            if (found == 0) {
 
4205
                freeifaddrs(ifa);
 
4206
                break;
 
4207
            }
 
4208
            sdlp = (struct sockaddr_dl *)ifp->ifa_addr;
 
4209
 
 
4210
            buf_check(sptr, s_end, 1+2+sdlp->sdl_alen);
 
4211
            *sptr++ = INET_IFOPT_HWADDR;
 
4212
            put_int16(sdlp->sdl_alen, sptr); sptr += 2;
 
4213
            sys_memcpy(sptr,
 
4214
                       sdlp->sdl_data + sdlp->sdl_nlen,
 
4215
                       sdlp->sdl_alen);
 
4216
            freeifaddrs(ifa);
 
4217
            sptr += sdlp->sdl_alen;
4175
4218
#endif
4176
4219
            break;
4177
4220
        }
4248
4291
 
4249
4292
        case INET_IFOPT_FLAGS: {
4250
4293
            int flags;
4251
 
            int eflags = 0;
4252
4294
 
4253
4295
            if (ioctl(desc->s, SIOCGIFFLAGS, (char*)&ifreq) < 0)
4254
4296
                flags = 0;
4255
4297
            else
4256
4298
                flags = ifreq.ifr_flags;
4257
 
            /* translate flags */
4258
 
            if (flags & IFF_UP)
4259
 
                eflags |= INET_IFF_UP;
4260
 
            if (flags & IFF_BROADCAST)
4261
 
                eflags |= INET_IFF_BROADCAST;
4262
 
            if (flags & IFF_LOOPBACK)
4263
 
                eflags |= INET_IFF_LOOPBACK;    
4264
 
            if (flags & IFF_POINTOPOINT)
4265
 
                eflags |= INET_IFF_POINTTOPOINT;
4266
 
            if (flags & IFF_RUNNING)
4267
 
                eflags |= INET_IFF_RUNNING;
4268
 
            if (flags & IFF_MULTICAST)
4269
 
                eflags |= INET_IFF_MULTICAST;
4270
4299
 
4271
4300
            buf_check(sptr, s_end, 5);
4272
4301
            *sptr++ = INET_IFOPT_FLAGS;
4273
 
            put_int32(eflags, sptr);
 
4302
            put_int32(IFGET_FLAGS(flags), sptr);
4274
4303
            sptr += 4;
4275
4304
            break;
4276
4305
        }
4284
4313
    return ctl_error(EINVAL, rbuf, rsize);
4285
4314
}
4286
4315
 
4287
 
/* FIXME: temporary hack */
4288
 
#ifndef IFHWADDRLEN
4289
 
#define IFHWADDRLEN 6
4290
 
#endif
4291
4316
 
4292
4317
static int inet_ctl_ifset(inet_descriptor* desc, char* buf, int len,
4293
4318
                          char** rbuf, int rsize)
4296
4321
    int namlen;
4297
4322
    char* b_end = buf + len;
4298
4323
 
4299
 
    if ((len == 0) || ((namlen = buf[0]) > len))
 
4324
    if ((len == 0) || ((namlen = get_int8(buf)) > len))
4300
4325
        goto error;
4301
4326
    sys_memset(ifreq.ifr_name, '\0', IFNAMSIZ);
4302
4327
    sys_memcpy(ifreq.ifr_name, buf+1, 
4303
 
               (namlen > IFNAMSIZ) ? IFNAMSIZ : namlen);
 
4328
               (namlen >= IFNAMSIZ) ? IFNAMSIZ-1 : namlen);
4304
4329
    buf += (namlen+1);
4305
4330
    len -= (namlen+1);
4306
4331
 
4312
4337
            (void) ioctl(desc->s, SIOCSIFADDR, (char*)&ifreq);
4313
4338
            break;
4314
4339
 
4315
 
        case INET_IFOPT_HWADDR: 
4316
 
            buf_check(buf, b_end, IFHWADDRLEN);
 
4340
        case INET_IFOPT_HWADDR: {
 
4341
            unsigned int len;
 
4342
            buf_check(buf, b_end, 2);
 
4343
            len = get_int16(buf); buf += 2;
 
4344
            buf_check(buf, b_end, len);
4317
4345
#ifdef SIOCSIFHWADDR
4318
4346
            /* raw memcpy (fix include autoconf later) */
4319
 
            sys_memcpy((char*)(&ifreq.ifr_hwaddr.sa_data), buf, IFHWADDRLEN);
 
4347
            sys_memset((char*)(&ifreq.ifr_hwaddr.sa_data),
 
4348
                       '\0', sizeof(ifreq.ifr_hwaddr.sa_data));
 
4349
            sys_memcpy((char*)(&ifreq.ifr_hwaddr.sa_data), buf, len);
4320
4350
 
4321
4351
            (void) ioctl(desc->s, SIOCSIFHWADDR, (char *)&ifreq);
4322
4352
#endif
4323
 
            buf += IFHWADDRLEN;
 
4353
            buf += len;
4324
4354
            break;
4325
 
 
 
4355
        }
4326
4356
 
4327
4357
        case INET_IFOPT_BROADADDR:
4328
4358
#ifdef SIOCSIFBRDADDR
4427
4457
 
4428
4458
#endif
4429
4459
 
 
4460
 
 
4461
 
 
4462
/* Latin-1 to utf8 */
 
4463
 
 
4464
static int utf8_len(const char *c, int m) {
 
4465
    int l;
 
4466
    for (l = 0;  m;  c++, l++, m--) {
 
4467
        if (*c == '\0') break;
 
4468
        if ((*c & 0x7f) != *c) l++;
 
4469
    }
 
4470
    return l;
 
4471
}
 
4472
 
 
4473
static void utf8_encode(const char *c, int m, char *p) {
 
4474
    for (;  m;  c++, m--) {
 
4475
        if (*c == '\0') break;
 
4476
        if ((*c & 0x7f) != *c) {
 
4477
            *p++ = (char) (0xC0 | (0x03 & (*c >> 6)));
 
4478
            *p++ = (char) (0x80 | (0x3F & *c));
 
4479
        } else {
 
4480
            *p++ = (char) *c;
 
4481
        }
 
4482
    }
 
4483
}
 
4484
 
 
4485
#if defined(__WIN32__)
 
4486
 
 
4487
static void set_netmask_bytes(char *c, int len, int pref_len) {
 
4488
    int i, m;
 
4489
    for (i = 0, m = pref_len >> 3;  i < m && i < len;  i++) c[i] = '\xFF';
 
4490
    if (i < len) c[i++] = 0xFF << (8 - (pref_len & 7));
 
4491
    for (;  i < len;  i++) c[i] = '\0';
 
4492
}
 
4493
 
 
4494
 
 
4495
int eq_masked_bytes(char *a, char *b, int pref_len) {
 
4496
    int i, m;
 
4497
    for (i = 0, m = pref_len >> 3;  i < m;  i++) {
 
4498
        if (a[i] != b[i]) return 0;
 
4499
    }
 
4500
    m = pref_len & 7;
 
4501
    if (m) {
 
4502
        m = 0xFF & (0xFF << (8 - m));
 
4503
        if ((a[i] & m) != (b[i] & m)) return 0;
 
4504
    }
 
4505
    return !0;
 
4506
}
 
4507
 
 
4508
static int inet_ctl_getifaddrs(inet_descriptor* desc_p,
 
4509
                               char **rbuf_pp, int rsize)
 
4510
{
 
4511
    int i;
 
4512
    DWORD ret, n;
 
4513
    IP_INTERFACE_INFO *info_p;
 
4514
    MIB_IPADDRTABLE *ip_addrs_p;
 
4515
    IP_ADAPTER_ADDRESSES *ip_adaddrs_p, *ia_p;
 
4516
 
 
4517
    char *buf_p;
 
4518
    char *buf_alloc_p;
 
4519
    int buf_size =512;
 
4520
#   define BUF_ENSURE(Size)                                             \
 
4521
    do {                                                                \
 
4522
        int NEED_, GOT_ = buf_p - buf_alloc_p;                          \
 
4523
        NEED_ = GOT_ + (Size);                                          \
 
4524
        if (NEED_ > buf_size) {                                         \
 
4525
            buf_size = NEED_ + 512;                                     \
 
4526
            buf_alloc_p = REALLOC(buf_alloc_p, buf_size);               \
 
4527
            buf_p = buf_alloc_p + GOT_;                                 \
 
4528
        }                                                               \
 
4529
    } while(0)
 
4530
#   define SOCKADDR_TO_BUF(opt, sa)                                     \
 
4531
    do {                                                                \
 
4532
        if (sa) {                                                       \
 
4533
            char *P_;                                                   \
 
4534
            *buf_p++ = (opt);                                           \
 
4535
            while (! (P_ = sockaddr_to_buf((sa), buf_p,                 \
 
4536
                                           buf_alloc_p+buf_size))) {    \
 
4537
                int GOT_ = buf_p - buf_alloc_p;                         \
 
4538
                buf_size += 512;                                        \
 
4539
                buf_alloc_p = REALLOC(buf_alloc_p, buf_size);           \
 
4540
                buf_p = buf_alloc_p + GOT_;                             \
 
4541
            }                                                           \
 
4542
            if (P_ == buf_p) {                                          \
 
4543
                buf_p--;                                                \
 
4544
            } else {                                                    \
 
4545
                buf_p = P_;                                             \
 
4546
            }                                                           \
 
4547
        }                                                               \
 
4548
    } while (0)
 
4549
 
 
4550
    {
 
4551
        /* Try GetAdaptersAddresses, if it is available */
 
4552
        unsigned long ip_adaddrs_size = 16 * 1024;
 
4553
        ULONG family = AF_UNSPEC;
 
4554
        ULONG flags =
 
4555
            GAA_FLAG_INCLUDE_PREFIX | GAA_FLAG_SKIP_ANYCAST |
 
4556
            GAA_FLAG_SKIP_DNS_SERVER | GAA_FLAG_SKIP_FRIENDLY_NAME |
 
4557
            GAA_FLAG_SKIP_MULTICAST;
 
4558
        ULONG (WINAPI *fpGetAdaptersAddresses)
 
4559
            (ULONG, ULONG, PVOID, PIP_ADAPTER_ADDRESSES, PULONG);
 
4560
        HMODULE iphlpapi = GetModuleHandle("iphlpapi");
 
4561
        fpGetAdaptersAddresses = (void *)
 
4562
            (iphlpapi ?
 
4563
                GetProcAddress(iphlpapi, "GetAdaptersAddresses") :
 
4564
                NULL);
 
4565
        if (fpGetAdaptersAddresses) {
 
4566
            ip_adaddrs_p = ALLOC(ip_adaddrs_size);
 
4567
            for (i = 17;  i;  i--) {
 
4568
                ret = fpGetAdaptersAddresses(
 
4569
                    family, flags, NULL, ip_adaddrs_p, &ip_adaddrs_size);
 
4570
                ip_adaddrs_p = REALLOC(ip_adaddrs_p, ip_adaddrs_size);
 
4571
                if (ret == NO_ERROR) break;
 
4572
                if (ret == ERROR_BUFFER_OVERFLOW) continue;
 
4573
                i = 0;
 
4574
            }
 
4575
            if (! i) {
 
4576
                FREE(ip_adaddrs_p);
 
4577
                ip_adaddrs_p = NULL;
 
4578
            }
 
4579
        } else ip_adaddrs_p = NULL;
 
4580
    }
 
4581
 
 
4582
    {
 
4583
        /* Load the IP_INTERFACE_INFO table (only IPv4 interfaces),
 
4584
         * reliable source of interface names on XP
 
4585
         */
 
4586
        unsigned long info_size = 4 * 1024;
 
4587
        info_p = ALLOC(info_size);
 
4588
        for (i = 17;  i;  i--) {
 
4589
            ret = GetInterfaceInfo(info_p, &info_size);
 
4590
            info_p = REALLOC(info_p, info_size);
 
4591
            if (ret == NO_ERROR) break;
 
4592
            if (ret == ERROR_INSUFFICIENT_BUFFER) continue;
 
4593
            i = 0;
 
4594
        }
 
4595
        if (! i) {
 
4596
            FREE(info_p);
 
4597
            info_p = NULL;
 
4598
        }
 
4599
    }
 
4600
 
 
4601
    if (! ip_adaddrs_p) {
 
4602
        /* If GetAdaptersAddresses gave nothing we fall back to
 
4603
         * MIB_IPADDRTABLE (only IPv4 interfaces)
 
4604
         */
 
4605
        unsigned long ip_addrs_size = 16 * sizeof(*ip_addrs_p);
 
4606
        ip_addrs_p = ALLOC(ip_addrs_size);
 
4607
        for (i = 17;  i;  i--) {
 
4608
            ret = GetIpAddrTable(ip_addrs_p, &ip_addrs_size, FALSE);
 
4609
            ip_addrs_p = REALLOC(ip_addrs_p, ip_addrs_size);
 
4610
            if (ret == NO_ERROR) break;
 
4611
            if (ret == ERROR_INSUFFICIENT_BUFFER) continue;
 
4612
            i = 0;
 
4613
        }
 
4614
        if (! i) {
 
4615
            if (info_p) FREE(info_p);
 
4616
            FREE(ip_addrs_p);
 
4617
            return ctl_reply(INET_REP_OK, NULL, 0, rbuf_pp, rsize);
 
4618
        }
 
4619
    } else ip_addrs_p = NULL;
 
4620
 
 
4621
    buf_p = buf_alloc_p = ALLOC(buf_size);
 
4622
    *buf_p++ = INET_REP_OK;
 
4623
 
 
4624
    /* Iterate over MIB_IPADDRTABLE or IP_ADAPTER_ADDRESSES */
 
4625
    for (ia_p = NULL, ip_addrs_p ? ((void *)(i = 0)) : (ia_p = ip_adaddrs_p);
 
4626
         ip_addrs_p ? (i < ip_addrs_p->dwNumEntries) : (ia_p != NULL);
 
4627
         ip_addrs_p ? ((void *)(i++)) : (ia_p = ia_p->Next)) {
 
4628
        MIB_IPADDRROW *ipaddrrow_p = NULL;
 
4629
        DWORD flags = INET_IFF_MULTICAST;
 
4630
        DWORD index = 0;
 
4631
        WCHAR *wname_p = NULL;
 
4632
        MIB_IFROW ifrow;
 
4633
 
 
4634
        if (ip_addrs_p) {
 
4635
            ipaddrrow_p = ip_addrs_p->table + i;
 
4636
            index = ipaddrrow_p->dwIndex;
 
4637
        } else {
 
4638
            index = ia_p->IfIndex;
 
4639
            if (ia_p->Flags & IP_ADAPTER_NO_MULTICAST) {
 
4640
                flags &= ~INET_IFF_MULTICAST;
 
4641
            }
 
4642
        }
 
4643
index:
 
4644
        if (! index) goto done;
 
4645
        sys_memzero(&ifrow, sizeof(ifrow));
 
4646
        ifrow.dwIndex = index;
 
4647
        if (GetIfEntry(&ifrow) != NO_ERROR) break;
 
4648
        /* Find the interface name - first try MIB_IFROW.wzname */
 
4649
        if (ifrow.wszName[0] != 0) {
 
4650
            wname_p = ifrow.wszName;
 
4651
        } else {
 
4652
            /* Then try IP_ADAPTER_INDEX_MAP.Name (only IPv4 adapters) */
 
4653
            int j;
 
4654
            for (j = 0;  j < info_p->NumAdapters;  j++) {
 
4655
                if (info_p->Adapter[j].Index == (ULONG) ifrow.dwIndex) {
 
4656
                    if (info_p->Adapter[j].Name[0] != 0) {
 
4657
                        wname_p = info_p->Adapter[j].Name;
 
4658
                    }
 
4659
                    break;
 
4660
                }
 
4661
            }
 
4662
        }
 
4663
        if (wname_p) {
 
4664
            int len;
 
4665
            /* Convert interface name to UTF-8 */
 
4666
            len =
 
4667
                WideCharToMultiByte(
 
4668
                    CP_UTF8, 0, wname_p, -1, NULL, 0, NULL, NULL);
 
4669
            if (! len) break;
 
4670
            BUF_ENSURE(len);
 
4671
            WideCharToMultiByte(
 
4672
                CP_UTF8, 0, wname_p, -1, buf_p, len, NULL, NULL);
 
4673
            buf_p += len;
 
4674
        } else {
 
4675
            /* Found no name -
 
4676
            * use "MIB_IFROW.dwIndex: MIB_IFROW.bDescr" as name instead */
 
4677
            int l;
 
4678
            l = utf8_len(ifrow.bDescr, ifrow.dwDescrLen);
 
4679
            BUF_ENSURE(9 + l+1);
 
4680
            buf_p +=
 
4681
                erts_sprintf(
 
4682
                    buf_p, "%lu: ", (unsigned long) ifrow.dwIndex);
 
4683
            utf8_encode(ifrow.bDescr, ifrow.dwDescrLen, buf_p);
 
4684
            buf_p += l;
 
4685
            *buf_p++ = '\0';
 
4686
        }
 
4687
        /* Interface flags, often make up broadcast and multicast flags */
 
4688
        switch (ifrow.dwType) {
 
4689
        case IF_TYPE_ETHERNET_CSMACD:
 
4690
            flags |= INET_IFF_BROADCAST;
 
4691
            break;
 
4692
        case IF_TYPE_SOFTWARE_LOOPBACK:
 
4693
            flags |= INET_IFF_LOOPBACK;
 
4694
            flags &= ~INET_IFF_MULTICAST;
 
4695
            break;
 
4696
        default:
 
4697
            flags &= ~INET_IFF_MULTICAST;
 
4698
            break;
 
4699
        }
 
4700
        if (ifrow.dwAdminStatus) {
 
4701
            flags |= INET_IFF_UP;
 
4702
            switch (ifrow.dwOperStatus) {
 
4703
            case IF_OPER_STATUS_CONNECTING:
 
4704
                flags |= INET_IFF_POINTTOPOINT;
 
4705
                break;
 
4706
            case IF_OPER_STATUS_CONNECTED:
 
4707
                flags |= INET_IFF_RUNNING | INET_IFF_POINTTOPOINT;
 
4708
                break;
 
4709
            case IF_OPER_STATUS_OPERATIONAL:
 
4710
                flags |= INET_IFF_RUNNING;
 
4711
                break;
 
4712
            }
 
4713
        }
 
4714
        BUF_ENSURE(1 + 4);
 
4715
        *buf_p++ = INET_IFOPT_FLAGS;
 
4716
        put_int32(flags, buf_p); buf_p += 4;
 
4717
        if (ipaddrrow_p) {
 
4718
            /* Legacy implementation through GetIpAddrTable */
 
4719
            struct sockaddr_in sin;
 
4720
            /* IP Address */
 
4721
            sys_memzero(&sin, sizeof(sin));
 
4722
            sin.sin_family = AF_INET;
 
4723
            sin.sin_addr.s_addr = ipaddrrow_p->dwAddr;
 
4724
            BUF_ENSURE(1);
 
4725
            /* Netmask */
 
4726
            SOCKADDR_TO_BUF(INET_IFOPT_ADDR, (struct sockaddr *) &sin);
 
4727
            sin.sin_addr.s_addr = ipaddrrow_p->dwMask;
 
4728
            BUF_ENSURE(1);
 
4729
            SOCKADDR_TO_BUF(INET_IFOPT_NETMASK, (struct sockaddr *) &sin);
 
4730
            if (flags & INET_IFF_BROADCAST) {
 
4731
                /* Broadcast address - fake it*/
 
4732
                sin.sin_addr.s_addr = ipaddrrow_p->dwAddr;
 
4733
                sin.sin_addr.s_addr |= ~ipaddrrow_p->dwMask;
 
4734
                BUF_ENSURE(1);
 
4735
                SOCKADDR_TO_BUF(
 
4736
                    INET_IFOPT_BROADADDR, (struct sockaddr *) &sin);
 
4737
            }
 
4738
        } else {
 
4739
            IP_ADAPTER_UNICAST_ADDRESS *p;
 
4740
            /* IP Address(es) */
 
4741
            for (p = ia_p->FirstUnicastAddress;
 
4742
                p;
 
4743
                p = p->Next)
 
4744
            {
 
4745
                IP_ADAPTER_PREFIX *q;
 
4746
                ULONG shortest_length;
 
4747
                struct sockaddr *shortest_p, *sa_p = p->Address.lpSockaddr;
 
4748
                BUF_ENSURE(1);
 
4749
                SOCKADDR_TO_BUF(INET_IFOPT_ADDR, sa_p);
 
4750
                shortest_p = NULL;
 
4751
                shortest_length = 0;
 
4752
                for (q = ia_p->FirstPrefix;
 
4753
                     q;
 
4754
                     q = q->Next) {
 
4755
                    struct sockaddr *sp_p = q->Address.lpSockaddr;
 
4756
                    if (sa_p->sa_family != sp_p->sa_family) continue;
 
4757
                    switch (sa_p->sa_family) {
 
4758
                    case AF_INET: {
 
4759
                        struct sockaddr_in sin;
 
4760
                        DWORD sa, sp, mask;
 
4761
                        sa = ntohl((DWORD)
 
4762
                                   ((struct sockaddr_in *)
 
4763
                                    sa_p)->sin_addr.s_addr);
 
4764
                        sp = ntohl((DWORD)
 
4765
                                   ((struct sockaddr_in *)
 
4766
                                    sp_p)->sin_addr.s_addr);
 
4767
                        mask = 0xFFFFFFFF << (32 - q->PrefixLength);
 
4768
                        if ((sa & mask) != (sp & mask)) continue;
 
4769
                        if ((! shortest_p)
 
4770
                            || q->PrefixLength < shortest_length) {
 
4771
                            shortest_p = sp_p;
 
4772
                            shortest_length = q->PrefixLength;
 
4773
                        }
 
4774
                    }   break;
 
4775
                    case AF_INET6: {
 
4776
                        struct sockaddr_in6 sin6;
 
4777
                        if (!eq_masked_bytes((char *)
 
4778
                                             &((struct sockaddr_in6 *)
 
4779
                                               sa_p)->sin6_addr,
 
4780
                                             (char *)
 
4781
                                             &((struct sockaddr_in6 *)
 
4782
                                               sp_p)->sin6_addr,
 
4783
                                             q->PrefixLength)) {
 
4784
                            continue;
 
4785
                        }
 
4786
                        if ((! shortest_p)
 
4787
                            || q->PrefixLength < shortest_length) {
 
4788
                            shortest_p = sp_p;
 
4789
                            shortest_length = q->PrefixLength;
 
4790
                        }
 
4791
                    }   break;
 
4792
                    }
 
4793
                }
 
4794
                if (! shortest_p) {
 
4795
                    /* Found no shortest prefix */
 
4796
                    shortest_p = sa_p;
 
4797
                    switch (shortest_p->sa_family) {
 
4798
                    case AF_INET: {
 
4799
                        /* Fall back to old classfull network addresses */
 
4800
                        DWORD addr = ntohl(((struct sockaddr_in *)shortest_p)
 
4801
                                           ->sin_addr.s_addr);
 
4802
                        if (! (addr & 0x800000)) {
 
4803
                            /* Class A */
 
4804
                            shortest_length = 8;
 
4805
                        } else if (! (addr & 0x400000)) {
 
4806
                            /* Class B */
 
4807
                            shortest_length = 16;
 
4808
                        } else if (! (addr & 0x200000)) {
 
4809
                            /* Class C */
 
4810
                            shortest_length = 24;
 
4811
                        } else {
 
4812
                            shortest_length = 32;
 
4813
                        }
 
4814
                    }   break;
 
4815
                    case AF_INET6: {
 
4816
                        /* Just play it safe */
 
4817
                        shortest_length = 128;
 
4818
                    }   break;
 
4819
                    }
 
4820
                }
 
4821
                switch (shortest_p->sa_family) {
 
4822
                case AF_INET: {
 
4823
                    struct sockaddr_in sin;
 
4824
                    DWORD mask = 0xFFFFFFFF << (32 - shortest_length);
 
4825
                    sys_memzero(&sin, sizeof(sin));
 
4826
                    sin.sin_family = shortest_p->sa_family;
 
4827
                    sin.sin_addr.s_addr = htonl(mask);
 
4828
                    BUF_ENSURE(1);
 
4829
                    SOCKADDR_TO_BUF(INET_IFOPT_NETMASK,
 
4830
                                    (struct sockaddr *) &sin);
 
4831
                    if (flags & INET_IFF_BROADCAST) {
 
4832
                        DWORD sp =
 
4833
                            ntohl((DWORD)
 
4834
                                  ((struct sockaddr_in *)shortest_p)
 
4835
                                  -> sin_addr.s_addr);
 
4836
                        sin.sin_addr.s_addr = htonl(sp | ~mask);
 
4837
                        BUF_ENSURE(1);
 
4838
                        SOCKADDR_TO_BUF(INET_IFOPT_BROADADDR,
 
4839
                                        (struct sockaddr *) &sin);
 
4840
                    }
 
4841
                }   break;
 
4842
                case AF_INET6: {
 
4843
                    struct sockaddr_in6 sin6;
 
4844
                    sys_memzero(&sin6, sizeof(sin6));
 
4845
                    sin6.sin6_family = shortest_p->sa_family;
 
4846
                    set_netmask_bytes((char *) &sin6.sin6_addr,
 
4847
                                      16,
 
4848
                                      shortest_length);
 
4849
                    BUF_ENSURE(1);
 
4850
                    SOCKADDR_TO_BUF(INET_IFOPT_NETMASK,
 
4851
                                    (struct sockaddr *) &sin6);
 
4852
                }   break;
 
4853
                }
 
4854
            }
 
4855
        }
 
4856
        if (ifrow.dwPhysAddrLen) {
 
4857
            /* Hardware Address */
 
4858
            BUF_ENSURE(1 + 2 + ifrow.dwPhysAddrLen);
 
4859
            *buf_p++ = INET_IFOPT_HWADDR;
 
4860
            put_int16(ifrow.dwPhysAddrLen, buf_p); buf_p += 2;
 
4861
            sys_memcpy(buf_p, ifrow.bPhysAddr, ifrow.dwPhysAddrLen);
 
4862
            buf_p += ifrow.dwPhysAddrLen;
 
4863
        }
 
4864
 
 
4865
done:
 
4866
        /* That is all for this interface */
 
4867
        BUF_ENSURE(1);
 
4868
        *buf_p++ = '\0';
 
4869
        if (ia_p &&
 
4870
            ia_p->Ipv6IfIndex &&
 
4871
            ia_p->Ipv6IfIndex != index)
 
4872
        {
 
4873
            /* Oops, there was an other interface for IPv6. Possible? XXX */
 
4874
            index = ia_p->Ipv6IfIndex;
 
4875
            goto index;
 
4876
        }
 
4877
    }
 
4878
 
 
4879
    if (ip_adaddrs_p) FREE(ip_adaddrs_p);
 
4880
    if (info_p) FREE(info_p);
 
4881
    if (ip_addrs_p) FREE(ip_addrs_p);
 
4882
 
 
4883
    buf_size = buf_p - buf_alloc_p;
 
4884
    buf_alloc_p = REALLOC(buf_alloc_p, buf_size);
 
4885
    /* buf_p is now unreliable */
 
4886
    *rbuf_pp = buf_alloc_p;
 
4887
    return buf_size;
 
4888
#   undef BUF_ENSURE
 
4889
}
 
4890
 
 
4891
#elif defined(HAVE_GETIFADDRS)
 
4892
 
 
4893
static int inet_ctl_getifaddrs(inet_descriptor* desc_p,
 
4894
                               char **rbuf_pp, int rsize)
 
4895
{
 
4896
    struct ifaddrs *ifa_p, *ifa_free_p;
 
4897
 
 
4898
    int buf_size;
 
4899
    char *buf_p;
 
4900
    char *buf_alloc_p;
 
4901
 
 
4902
    buf_size = 512;
 
4903
    buf_alloc_p = ALLOC(buf_size);
 
4904
    buf_p = buf_alloc_p;
 
4905
#   define BUF_ENSURE(Size)                                             \
 
4906
    do {                                                                \
 
4907
        int NEED_, GOT_ = buf_p - buf_alloc_p;                          \
 
4908
        NEED_ = GOT_ + (Size);                                          \
 
4909
        if (NEED_ > buf_size) {                                         \
 
4910
            buf_size = NEED_ + 512;                                     \
 
4911
            buf_alloc_p = REALLOC(buf_alloc_p, buf_size);               \
 
4912
            buf_p = buf_alloc_p + GOT_;                                 \
 
4913
        }                                                               \
 
4914
    } while (0)
 
4915
#   define SOCKADDR_TO_BUF(opt, sa)                                     \
 
4916
    do {                                                                \
 
4917
        if (sa) {                                                       \
 
4918
            char *P_;                                                   \
 
4919
            *buf_p++ = (opt);                                           \
 
4920
            while (! (P_ = sockaddr_to_buf((sa), buf_p,                 \
 
4921
                                           buf_alloc_p+buf_size))) {    \
 
4922
                int GOT_ = buf_p - buf_alloc_p;                         \
 
4923
                buf_size += 512;                                        \
 
4924
                buf_alloc_p = REALLOC(buf_alloc_p, buf_size);           \
 
4925
                buf_p = buf_alloc_p + GOT_;                             \
 
4926
            }                                                           \
 
4927
            if (P_ == buf_p) {                                          \
 
4928
                buf_p--;                                                \
 
4929
            } else {                                                    \
 
4930
                buf_p = P_;                                             \
 
4931
            }                                                           \
 
4932
        }                                                               \
 
4933
    } while (0)
 
4934
 
 
4935
    if (getifaddrs(&ifa_p) < 0) {
 
4936
        return ctl_error(sock_errno(), rbuf_pp, rsize);
 
4937
    }
 
4938
    ifa_free_p = ifa_p;
 
4939
    *buf_p++ = INET_REP_OK;
 
4940
    for (;  ifa_p;  ifa_p = ifa_p->ifa_next) {
 
4941
        int len = utf8_len(ifa_p->ifa_name, -1);
 
4942
        BUF_ENSURE(len+1 + 1+4 + 1);
 
4943
        utf8_encode(ifa_p->ifa_name, -1, buf_p);
 
4944
        buf_p += len;
 
4945
        *buf_p++ = '\0';
 
4946
        *buf_p++ = INET_IFOPT_FLAGS;
 
4947
        put_int32(IFGET_FLAGS(ifa_p->ifa_flags), buf_p); buf_p += 4;
 
4948
        if (ifa_p->ifa_addr) {
 
4949
            if (ifa_p->ifa_addr->sa_family == AF_INET
 
4950
#if defined(AF_INET6)
 
4951
                || ifa_p->ifa_addr->sa_family == AF_INET6
 
4952
#endif
 
4953
                ) {
 
4954
                SOCKADDR_TO_BUF(INET_IFOPT_ADDR, ifa_p->ifa_addr);
 
4955
                if (ifa_p->ifa_netmask) {
 
4956
                    BUF_ENSURE(1);
 
4957
                    SOCKADDR_TO_BUF(INET_IFOPT_NETMASK, ifa_p->ifa_netmask);
 
4958
                }
 
4959
                if (ifa_p->ifa_dstaddr &&
 
4960
                    (ifa_p->ifa_flags & IFF_POINTOPOINT)) {
 
4961
                    BUF_ENSURE(1);
 
4962
                    SOCKADDR_TO_BUF(INET_IFOPT_DSTADDR, ifa_p->ifa_dstaddr);
 
4963
                } else if (ifa_p->ifa_broadaddr &&
 
4964
                           (ifa_p->ifa_flags & IFF_BROADCAST)) {
 
4965
                    BUF_ENSURE(1);
 
4966
                    SOCKADDR_TO_BUF(INET_IFOPT_BROADADDR, ifa_p->ifa_broadaddr);
 
4967
                }
 
4968
            }
 
4969
#if defined(AF_LINK) || defined(AF_PACKET)
 
4970
            else if (
 
4971
#if defined(AF_LINK)
 
4972
                     ifa_p->ifa_addr->sa_family == AF_LINK
 
4973
#else
 
4974
                     0
 
4975
#endif
 
4976
#if defined(AF_PACKET)
 
4977
                     || ifa_p->ifa_addr->sa_family == AF_PACKET
 
4978
#endif
 
4979
                     ) {
 
4980
                char *bp = buf_p;
 
4981
                BUF_ENSURE(1);
 
4982
                SOCKADDR_TO_BUF(INET_IFOPT_HWADDR, ifa_p->ifa_addr);
 
4983
                if (buf_p - bp < 4) buf_p = bp; /* Empty hwaddr */
 
4984
            }
 
4985
#endif
 
4986
        }
 
4987
        BUF_ENSURE(1);
 
4988
        *buf_p++ = '\0';
 
4989
    }
 
4990
    buf_size = buf_p - buf_alloc_p;
 
4991
    buf_alloc_p = REALLOC(buf_alloc_p, buf_size);
 
4992
    /* buf_p is now unreliable */
 
4993
    freeifaddrs(ifa_free_p);
 
4994
    *rbuf_pp = buf_alloc_p;
 
4995
    return buf_size;
 
4996
#   undef BUF_ENSURE
 
4997
}
 
4998
 
 
4999
#else
 
5000
 
 
5001
static int inet_ctl_getifaddrs(inet_descriptor* desc_p,
 
5002
                               char **rbuf_pp, int rsize)
 
5003
{
 
5004
    return ctl_error(ENOTSUP, rbuf_pp, rsize);
 
5005
}
 
5006
 
 
5007
#endif
 
5008
 
 
5009
 
 
5010
 
4430
5011
#ifdef VXWORKS
4431
5012
/*
4432
5013
** THIS is a terrible creature, a bug in the TCP part
4469
5050
}
4470
5051
#endif
4471
5052
 
 
5053
/* Per H @ Tail-f: The original code here had problems that possibly
 
5054
   only occur if you abuse it for non-INET sockets, but anyway:
 
5055
   a) If the getsockopt for SO_PRIORITY or IP_TOS failed, the actual
 
5056
      requested setsockopt was never even attempted.
 
5057
   b) If {get,set}sockopt for one of IP_TOS and SO_PRIORITY failed,
 
5058
      but ditto for the other worked and that was actually the requested
 
5059
      option, failure was still reported to erlang.                  */
 
5060
 
4472
5061
#if  defined(IP_TOS) && defined(SOL_IP) && defined(SO_PRIORITY)
4473
5062
static int setopt_prio_tos_trick
4474
 
           (int fd, int proto, int type, char* arg_ptr, int arg_sz)
 
5063
        (int fd, int proto, int type, char* arg_ptr, int arg_sz, int propagate)
4475
5064
{
4476
5065
    /* The relations between SO_PRIORITY, TOS and other options
4477
5066
       is not what you (or at least I) would expect...:
4484
5073
    int          tmp_ival_prio;
4485
5074
    int          tmp_ival_tos;
4486
5075
    int          res;
 
5076
    int          res_prio;
 
5077
    int          res_tos;
4487
5078
#ifdef HAVE_SOCKLEN_T
4488
5079
            socklen_t
4489
5080
#else
4492
5083
                tmp_arg_sz_prio = sizeof(tmp_ival_prio),
4493
5084
                tmp_arg_sz_tos  = sizeof(tmp_ival_tos);
4494
5085
 
4495
 
    res = sock_getopt(fd, SOL_SOCKET, SO_PRIORITY,
 
5086
    res_prio = sock_getopt(fd, SOL_SOCKET, SO_PRIORITY,
4496
5087
                      (char *) &tmp_ival_prio, &tmp_arg_sz_prio);
4497
 
    if (res == 0) {
4498
 
        res = sock_getopt(fd, SOL_IP, IP_TOS, 
 
5088
    res_tos = sock_getopt(fd, SOL_IP, IP_TOS, 
4499
5089
                      (char *) &tmp_ival_tos, &tmp_arg_sz_tos);
4500
 
        if (res == 0) {
4501
5090
            res = sock_setopt(fd, proto, type, arg_ptr, arg_sz);
4502
5091
            if (res == 0) {
4503
5092
                if (type != SO_PRIORITY) {
4504
 
                    if (type != IP_TOS) {
4505
 
                        res = sock_setopt(fd, 
 
5093
            if (type != IP_TOS && res_tos == 0) {
 
5094
                res_tos = sock_setopt(fd, 
4506
5095
                                          SOL_IP, 
4507
5096
                                          IP_TOS,
4508
5097
                                          (char *) &tmp_ival_tos, 
4509
5098
                                          tmp_arg_sz_tos);
 
5099
                if (propagate)
 
5100
                    res = res_tos;
4510
5101
                    }
4511
 
                    if (res == 0) {
4512
 
                        res =  sock_setopt(fd, 
 
5102
            if (res == 0 && res_prio == 0) {
 
5103
                res_prio = sock_setopt(fd, 
4513
5104
                                           SOL_SOCKET, 
4514
5105
                                           SO_PRIORITY,
4515
5106
                                           (char *) &tmp_ival_prio, 
4516
5107
                                           tmp_arg_sz_prio);
 
5108
                if (propagate) {                
 
5109
                    /* Some kernels set a SO_PRIORITY by default that you are not permitted to reset,
 
5110
                       silently ignore this error condition */
 
5111
                    if (res_prio != 0 && sock_errno() == EPERM) {
 
5112
                        res = 0;
 
5113
                    } else {
 
5114
                        res = res_prio;
4517
5115
                    }
4518
5116
                }
4519
5117
            }
4588
5186
        case INET_LOPT_BUFFER:
4589
5187
            DEBUGF(("inet_set_opts(%ld): s=%d, BUFFER=%d\r\n",
4590
5188
                    (long)desc->port, desc->s, ival));
4591
 
            if (ival > INET_MAX_BUFFER)  ival = INET_MAX_BUFFER;
4592
 
            else if (ival < INET_MIN_BUFFER) ival = INET_MIN_BUFFER;
 
5189
            if (ival < INET_MIN_BUFFER) ival = INET_MIN_BUFFER;
4593
5190
            desc->bufsz = ival;
4594
5191
            continue;
4595
5192
 
4654
5251
            if (desc->stype == SOCK_STREAM) {
4655
5252
                tcp_descriptor* tdesc = (tcp_descriptor*) desc;
4656
5253
                if (ival < 0) ival = 0;
4657
 
                else if (ival > INET_MAX_BUFFER*2) ival = INET_MAX_BUFFER*2;
4658
5254
                if (tdesc->low > ival)
4659
5255
                    tdesc->low = ival;
4660
5256
                tdesc->high = ival;
4665
5261
            if (desc->stype == SOCK_STREAM) {
4666
5262
                tcp_descriptor* tdesc = (tcp_descriptor*) desc;
4667
5263
                if (ival < 0) ival = 0;
4668
 
                else if (ival > INET_MAX_BUFFER) ival = INET_MAX_BUFFER;
4669
5264
                if (tdesc->high < ival)
4670
5265
                    tdesc->high = ival;
4671
5266
                tdesc->low = ival;
4862
5457
            return -1;
4863
5458
        }
4864
5459
#if  defined(IP_TOS) && defined(SOL_IP) && defined(SO_PRIORITY)
4865
 
        res = setopt_prio_tos_trick (desc->s, proto, type, arg_ptr, arg_sz);
 
5460
        res = setopt_prio_tos_trick (desc->s, proto, type, arg_ptr, arg_sz, propagate);
4866
5461
#else
4867
5462
        res = sock_setopt           (desc->s, proto, type, arg_ptr, arg_sz);
4868
5463
#endif
5011
5606
        case INET_LOPT_BUFFER:
5012
5607
            desc->bufsz  = get_int32(curr);             curr += 4;
5013
5608
 
5014
 
            if (desc->bufsz > INET_MAX_BUFFER)
5015
 
                desc->bufsz = INET_MAX_BUFFER;
5016
 
            else
5017
5609
            if (desc->bufsz < INET_MIN_BUFFER)
5018
5610
                desc->bufsz = INET_MIN_BUFFER;
5019
5611
            res = 0;      /* This does not affect the kernel buffer size */
5076
5668
        }
5077
5669
        case INET_OPT_LINGER:
5078
5670
        {
5079
 
            CHKLEN(curr, ASSOC_ID_LEN + 2 + 4);
5080
 
            arg.lin.l_onoff  = get_int16 (curr);  curr += 2;
 
5671
            CHKLEN(curr, 2*4);
 
5672
            arg.lin.l_onoff  = get_int32 (curr);  curr += 4;
5081
5673
            arg.lin.l_linger = get_int32 (curr);  curr += 4;
5082
5674
 
5083
5675
            proto   = SOL_SOCKET;
5254
5846
            char *after;
5255
5847
#           ifdef HAVE_STRUCT_SCTP_PADDRPARAMS_SPP_FLAGS
5256
5848
            int eflags, cflags, hb_enable, hb_disable,
5257
 
                pmtud_enable, pmtud_disable,
 
5849
                pmtud_enable, pmtud_disable;
 
5850
#           ifdef HAVE_STRUCT_SCTP_PADDRPARAMS_SPP_SACKDELAY
 
5851
            int
5258
5852
                sackdelay_enable, sackdelay_disable;
5259
5853
#           endif
 
5854
#           endif
5260
5855
            
5261
5856
            CHKLEN(curr, ASSOC_ID_LEN);
5262
5857
            arg.pap.spp_assoc_id = GET_ASSOC_ID(curr);  curr += ASSOC_ID_LEN;
5305
5900
            if (pmtud_enable)                   cflags |= SPP_PMTUD_ENABLE;
5306
5901
            if (pmtud_disable)                  cflags |= SPP_PMTUD_DISABLE;
5307
5902
 
 
5903
#           ifdef HAVE_STRUCT_SCTP_PADDRPARAMS_SPP_SACKDELAY
 
5904
            /* The followings are missing in FreeBSD 7.1 */
5308
5905
            sackdelay_enable =eflags& SCTP_FLAG_SACDELAY_ENABLE;
5309
5906
            sackdelay_disable=eflags& SCTP_FLAG_SACDELAY_DISABLE;
5310
5907
            if (sackdelay_enable && sackdelay_disable)
5311
5908
                return -1;
5312
5909
            if (sackdelay_enable)               cflags |= SPP_SACKDELAY_ENABLE;
5313
5910
            if (sackdelay_disable)              cflags |= SPP_SACKDELAY_DISABLE;
 
5911
#           endif
5314
5912
 
5315
5913
            arg.pap.spp_flags  = cflags;
5316
5914
#           endif
5389
5987
            return -1;
5390
5988
        }
5391
5989
#if  defined(IP_TOS) && defined(SOL_IP) && defined(SO_PRIORITY)
5392
 
        res = setopt_prio_tos_trick (desc->s, proto, type, arg_ptr, arg_sz);
 
5990
        res = setopt_prio_tos_trick (desc->s, proto, type, arg_ptr, arg_sz, 1);
5393
5991
#else
5394
5992
        res = sock_setopt           (desc->s, proto, type, arg_ptr, arg_sz);
5395
5993
#endif
5448
6046
#define PLACE_FOR(Size,Ptr)                                                \
5449
6047
    do {                                                                   \
5450
6048
        int need = dest_used + (Size);                                     \
5451
 
        if (need > INET_MAX_BUFFER) {                                      \
 
6049
        if (need > INET_MAX_OPT_BUFFER) {                                  \
5452
6050
            RETURN_ERROR();                                                \
5453
6051
        }                                                                  \
5454
6052
        if (need > dest_allocated) {                                       \
5672
6270
                buf += 4;
5673
6271
                data_provided = (int) *buf++;
5674
6272
                arg_sz = get_int32(buf);
5675
 
                if (arg_sz > INET_MAX_BUFFER) { 
 
6273
                if (arg_sz > INET_MAX_OPT_BUFFER) {
5676
6274
                    RETURN_ERROR();
5677
6275
                }
5678
6276
                buf += 4;
5687
6285
                    buf += arg_sz;
5688
6286
                    len -= arg_sz;
5689
6287
                }
5690
 
                if (sock_getopt(desc->s,proto,type,arg_ptr,&arg_sz) == 
5691
 
                    SOCKET_ERROR) {
 
6288
                if (IS_SOCKET_ERROR(sock_getopt(desc->s,proto,type,
 
6289
                                                arg_ptr,&arg_sz))) {
5692
6290
                    TRUNCATE_TO(0,ptr); 
5693
6291
                    continue;
5694
6292
                }
5705
6303
            RETURN_ERROR();
5706
6304
        }
5707
6305
        /* We have 5 bytes allocated to ptr */
5708
 
        if (sock_getopt(desc->s,proto,type,arg_ptr,&arg_sz) == SOCKET_ERROR) {
 
6306
        if (IS_SOCKET_ERROR(sock_getopt(desc->s,proto,type,arg_ptr,&arg_sz))) {
5709
6307
            TRUNCATE_TO(0,ptr);
5710
6308
            continue;
5711
6309
        }
5786
6384
                     "miscalculated buffer size");              \
5787
6385
        }                                                       \
5788
6386
        need = (Index) + (N);                                   \
5789
 
        if (need > INET_MAX_BUFFER/sizeof(ErlDrvTermData)) {    \
 
6387
        if (need > INET_MAX_OPT_BUFFER/sizeof(ErlDrvTermData)) {\
5790
6388
            RETURN_ERROR((Spec), -ENOMEM);                      \
5791
6389
        }                                                       \
5792
6390
        if (need > spec_allocated) {                            \
6211
6809
            
6212
6810
            if (ap.spp_flags & SPP_PMTUD_DISABLE)
6213
6811
                { i = LOAD_ATOM (spec, i, am_pmtud_disable);         n++; }
6214
 
            
 
6812
#           ifdef HAVE_STRUCT_SCTP_PADDRPARAMS_SPP_SACKDELAY
 
6813
            /* SPP_SACKDELAY_* not in FreeBSD 7.1 */
6215
6814
            if (ap.spp_flags & SPP_SACKDELAY_ENABLE)
6216
6815
                { i = LOAD_ATOM (spec, i, am_sackdelay_enable);      n++; }
6217
6816
            
6218
6817
            if (ap.spp_flags & SPP_SACKDELAY_DISABLE)
6219
6818
                { i = LOAD_ATOM (spec, i, am_sackdelay_disable);     n++; }
6220
6819
#           endif
 
6820
#           endif
6221
6821
            
6222
6822
            PLACE_FOR(spec, i,
6223
6823
                      LOAD_NIL_CNT + LOAD_LIST_CNT + 2*LOAD_TUPLE_CNT);
6237
6837
            struct       sctp_sndrcvinfo sri;
6238
6838
            unsigned int sz  = sizeof(sri);
6239
6839
            
 
6840
            if (buflen < ASSOC_ID_LEN) RETURN_ERROR(spec, -EINVAL);
 
6841
            sri.sinfo_assoc_id = GET_ASSOC_ID(buf);
 
6842
            buf += ASSOC_ID_LEN;
 
6843
            buflen -= ASSOC_ID_LEN;
6240
6844
            if (sock_getopt(desc->s, IPPROTO_SCTP, SCTP_DEFAULT_SEND_PARAM,
6241
6845
                            &sri, &sz) < 0) continue;
6242
6846
            /* Fill in the response: */
6633
7237
              }
6634
7238
          }
6635
7239
          DEBUGF(("inet_ctl(%ld): GETSTAT\r\n", (long) desc->port)); 
6636
 
          if (dstlen > INET_MAX_BUFFER) /* sanity check */
 
7240
          if (dstlen > INET_MAX_OPT_BUFFER) /* sanity check */
6637
7241
              return 0;
6638
7242
          if (dstlen > rsize) {
6639
7243
              if ((dst = (char*) ALLOC(dstlen)) == NULL)
6649
7253
          char* dst;
6650
7254
          int dstlen = 1 /* Reply code */ + len*5;
6651
7255
          DEBUGF(("inet_ctl(%ld): INET_REQ_SUBSCRIBE\r\n", (long) desc->port)); 
6652
 
          if (dstlen > INET_MAX_BUFFER) /* sanity check */
 
7256
          if (dstlen > INET_MAX_OPT_BUFFER) /* sanity check */
6653
7257
              return 0;
6654
7258
          if (dstlen > rsize) {
6655
7259
              if ((dst = (char*) ALLOC(dstlen)) == NULL)
6684
7288
        return inet_ctl_getiflist(desc, rbuf, rsize);
6685
7289
    }
6686
7290
 
 
7291
    case INET_REQ_GETIFADDRS: {
 
7292
        DEBUGF(("inet_ctl(%ld): GETIFADDRS\r\n", (long)desc->port));
 
7293
        if (!IS_OPEN(desc))
 
7294
            return ctl_xerror(EXBADPORT, rbuf, rsize);
 
7295
        return inet_ctl_getifaddrs(desc, rbuf, rsize);
 
7296
    }
 
7297
 
6687
7298
    case INET_REQ_IFGET: {
6688
7299
        DEBUGF(("inet_ctl(%ld): IFGET\r\n", (long)desc->port));         
6689
7300
        if (!IS_OPEN(desc))
6771
7382
        if (len != 0)
6772
7383
            return ctl_error(EINVAL, rbuf, rsize);
6773
7384
 
6774
 
        if (sock_hostname(tbuf, MAXHOSTNAMELEN) == SOCKET_ERROR)
 
7385
        if (IS_SOCKET_ERROR(sock_hostname(tbuf, MAXHOSTNAMELEN)))
6775
7386
            return ctl_error(sock_errno(), rbuf, rsize);
6776
7387
        return ctl_reply(INET_REP_OK, tbuf, strlen(tbuf), rbuf, rsize);
6777
7388
    }
6788
7399
            return ctl_error(ENOTCONN, rbuf, rsize);
6789
7400
        if ((ptr = desc->peer_ptr) == NULL) {
6790
7401
            ptr = &peer;
6791
 
            if (sock_peer(desc->s, (struct sockaddr*)ptr,&sz) == SOCKET_ERROR)
 
7402
            if (IS_SOCKET_ERROR(sock_peer(desc->s, (struct sockaddr*)ptr,&sz)))
6792
7403
                return ctl_error(sock_errno(), rbuf, rsize);
6793
7404
        }
6794
7405
        if (inet_get_address(desc->sfamily, tbuf, ptr, &sz) < 0)
6825
7436
 
6826
7437
        if ((ptr = desc->name_ptr) == NULL) {
6827
7438
            ptr = &name;
6828
 
            if (sock_name(desc->s, (struct sockaddr*)ptr, &sz) == SOCKET_ERROR)
 
7439
            if (IS_SOCKET_ERROR(sock_name(desc->s, (struct sockaddr*)ptr, &sz)))
6829
7440
                return ctl_error(sock_errno(), rbuf, rsize);
6830
7441
        }
6831
7442
        if (inet_get_address(desc->sfamily, tbuf, ptr, &sz) < 0)
6864
7475
        if (inet_set_address(desc->sfamily, &local, buf, &len) == NULL)
6865
7476
            return ctl_error(EINVAL, rbuf, rsize);
6866
7477
 
6867
 
        if (sock_bind(desc->s,(struct sockaddr*) &local, len) == SOCKET_ERROR)
 
7478
        if (IS_SOCKET_ERROR(sock_bind(desc->s,(struct sockaddr*) &local, len)))
6868
7479
            return ctl_error(sock_errno(), rbuf, rsize);
6869
7480
 
6870
7481
        desc->state = INET_STATE_BOUND;
6891
7502
 
6892
7503
        if (len < 2)
6893
7504
            return ctl_error(EINVAL, rbuf, rsize);
6894
 
        n = buf[0]; buf++; len--;
 
7505
        n = get_int8(buf); buf++; len--;
6895
7506
        if (n >= len) /* the = sign makes the test inklude next length byte */
6896
7507
            return ctl_error(EINVAL, rbuf, rsize);
6897
7508
        memcpy(namebuf, buf, n);
6898
7509
        namebuf[n] = '\0';
6899
7510
        len -= n; buf += n;
6900
 
        n = buf[0]; buf++; len--;
 
7511
        n = get_int8(buf); buf++; len--;
6901
7512
        if (n > len)
6902
7513
            return ctl_error(EINVAL, rbuf, rsize);
6903
7514
        memcpy(protobuf, buf, n);
6920
7531
        port = get_int16(buf);
6921
7532
        port = sock_htons(port);
6922
7533
        buf += 2;
6923
 
        n = buf[0]; buf++; len -= 3;
 
7534
        n = get_int8(buf); buf++; len -= 3;
6924
7535
        if (n > len)
6925
7536
            return ctl_error(EINVAL, rbuf, rsize);
6926
7537
        memcpy(protobuf, buf, n);
7297
7908
        if (len != 2)
7298
7909
            return ctl_error(EINVAL, rbuf, rsize);
7299
7910
        backlog = get_int16(buf);
7300
 
        if (sock_listen(desc->inet.s, backlog) == SOCKET_ERROR)
 
7911
        if (IS_SOCKET_ERROR(sock_listen(desc->inet.s, backlog)))
7301
7912
            return ctl_error(sock_errno(), rbuf, rsize);
7302
7913
        desc->inet.state = TCP_STATE_LISTEN;
7303
7914
        return ctl_reply(INET_REP_OK, NULL, 0, rbuf, rsize);
7331
7942
        
7332
7943
        code = sock_connect(desc->inet.s, 
7333
7944
                            (struct sockaddr*) &desc->inet.remote, len);
7334
 
        if ((code == SOCKET_ERROR) && 
 
7945
        if (IS_SOCKET_ERROR(code) &&
7335
7946
                ((sock_errno() == ERRNO_BLOCK) ||  /* Winsock2 */
7336
7947
                 (sock_errno() == EINPROGRESS))) {      /* Unix & OSE!! */
7337
7948
          sock_select(INETP(desc), FD_CONNECT, 1);
7518
8129
            tcp_deliver(desc, 0);
7519
8130
        return ctl_reply(INET_REP_OK, NULL, 0, rbuf, rsize);
7520
8131
    }
7521
 
#ifndef _OSE_
7522
8132
    case TCP_REQ_SHUTDOWN: {
7523
8133
        int how;
7524
8134
        DEBUGF(("tcp_inet_ctl(%ld): FDOPEN\r\n", (long)desc->inet.port)); 
7535
8145
            return ctl_error(sock_errno(), rbuf, rsize);
7536
8146
        }
7537
8147
    }
7538
 
#endif
7539
8148
    default:
7540
8149
        DEBUGF(("tcp_inet_ctl(%ld): %u\r\n", (long)desc->inet.port, cmd)); 
7541
8150
        return inet_ctl(INETP(desc), cmd, buf, len, rbuf, rsize);
8009
8618
 
8010
8619
    n = sock_recv(desc->inet.s, desc->i_ptr, nread, 0);
8011
8620
 
8012
 
    if (n == SOCKET_ERROR) {
 
8621
    if (IS_SOCKET_ERROR(n)) {
8013
8622
        int err = sock_errno();
8014
8623
        if (err == ECONNRESET) {
8015
8624
            DEBUGF((" => detected close (connreset)\r\n"));
8511
9120
                (long)desc->inet.port, desc->inet.s, h_len, len));
8512
9121
        if (desc->tcp_add_flags & TCP_ADDF_DELAY_SEND) {
8513
9122
            n = 0;
8514
 
        } else if (sock_sendv(desc->inet.s, ev->iov, vsize, &n, 0) 
8515
 
                   == SOCKET_ERROR) {
 
9123
        } else if (IS_SOCKET_ERROR(sock_sendv(desc->inet.s, ev->iov,
 
9124
                                              vsize, &n, 0))) {
8516
9125
            if ((sock_errno() != ERRNO_BLOCK) && (sock_errno() != EINTR)) {
8517
9126
                int err = sock_errno();
8518
9127
                DEBUGF(("tcp_sendv(%ld): s=%d, "
8605
9214
        if (desc->tcp_add_flags & TCP_ADDF_DELAY_SEND) {
8606
9215
            sock_send(desc->inet.s, buf, 0, 0);
8607
9216
            n = 0;
8608
 
        } else  if (sock_sendv(desc->inet.s,iov,2,&n,0) == SOCKET_ERROR) {
 
9217
        } else  if (IS_SOCKET_ERROR(sock_sendv(desc->inet.s,iov,2,&n,0))) {
8609
9218
            if ((sock_errno() != ERRNO_BLOCK) && (sock_errno() != EINTR)) {
8610
9219
                int err = sock_errno();
8611
9220
                DEBUGF(("tcp_send(%ld): s=%d,sock_sendv(size=2) errno = %d\r\n",
8678
9287
            int code = sock_peer(desc->inet.s,
8679
9288
                                 (struct sockaddr*) &desc->inet.remote, &sz);
8680
9289
 
8681
 
            if (code == SOCKET_ERROR) {
 
9290
            if (IS_SOCKET_ERROR(code)) {
8682
9291
                desc->inet.state = TCP_STATE_BOUND;  /* restore state */
8683
9292
                ret =  async_error(INETP(desc), sock_errno());
8684
9293
                goto done;
8719
9328
            vsize = vsize > MAX_VSIZE ? MAX_VSIZE : vsize;
8720
9329
            DEBUGF(("tcp_inet_output(%ld): s=%d, About to send %d items\r\n", 
8721
9330
                    (long)desc->inet.port, desc->inet.s, vsize));
8722
 
            if (sock_sendv(desc->inet.s, iov, vsize, &n, 0)==SOCKET_ERROR) {
 
9331
            if (IS_SOCKET_ERROR(sock_sendv(desc->inet.s, iov, vsize, &n, 0))) {
8723
9332
                if ((sock_errno() != ERRNO_BLOCK) && (sock_errno() != EINTR)) {
8724
9333
                    DEBUGF(("tcp_inet_output(%ld): sock_sendv(%d) errno = %d\r\n",
8725
9334
                            (long)desc->inet.port, vsize, sock_errno()));
8988
9597
            sock_select(desc, FD_CONNECT, 1);
8989
9598
            code = sock_connect(desc->s, &remote.sa, len);
8990
9599
 
8991
 
            if ((code == SOCKET_ERROR) && (sock_errno() == EINPROGRESS)) {
 
9600
            if (IS_SOCKET_ERROR(code) && (sock_errno() == EINPROGRESS)) {
8992
9601
                /* XXX: Unix only -- WinSock would have a different cond! */
8993
9602
                desc->state = SCTP_STATE_CONNECTING;
8994
9603
                if (timeout != INET_INFINITY)
9028
9637
            
9029
9638
            code = sock_connect(desc->s,
9030
9639
                                (struct sockaddr*) &desc->remote, len);
9031
 
            if (code == SOCKET_ERROR) {
 
9640
            if (IS_SOCKET_ERROR(code)) {
9032
9641
                sock_connect(desc->s, (struct sockaddr*) NULL, 0);
9033
9642
                desc->state &= ~INET_F_ACTIVE;
9034
9643
                return ctl_error(sock_errno(), rbuf, rsize);
9062
9671
                return ctl_error(EINVAL, rbuf, rsize);
9063
9672
            flag = get_int8(buf);
9064
9673
 
9065
 
            if (sock_listen(desc->s, flag) == SOCKET_ERROR)
 
9674
            if (IS_SOCKET_ERROR(sock_listen(desc->s, flag)))
9066
9675
                return ctl_error(sock_errno(), rbuf, rsize);
9067
9676
 
9068
9677
            desc->state = SCTP_STATE_LISTEN;   /* XXX: not used? */
9267
9876
 check_result_code:
9268
9877
    /* "code" analysis is the same for both SCTP and UDP cases above: */
9269
9878
#endif
9270
 
    if (code == SOCKET_ERROR) {
 
9879
    if (IS_SOCKET_ERROR(code)) {
9271
9880
        int err = sock_errno();
9272
9881
        inet_reply_error(desc, err);
9273
9882
    }
9366
9975
    check_result:
9367
9976
#endif
9368
9977
        /* Analyse the result: */
9369
 
        if (n == SOCKET_ERROR
 
9978
        if (IS_SOCKET_ERROR(n)
9370
9979
#ifdef HAVE_SCTP
9371
9980
            || (short_recv = (IS_SCTP(desc) && !(mhdr.msg_flags & MSG_EOR)))
9372
9981
            /* NB: here we check for EOR not being set -- this is an error as
9379
9988
            if (err != ERRNO_BLOCK) {
9380
9989
                if (!desc->active) {
9381
9990
#ifdef HAVE_SCTP
9382
 
                    if (short_recv)
 
9991
                    if (short_recv) {
9383
9992
                        async_error_am(desc, am_short_recv);
9384
 
                    else
9385
 
#else
 
9993
                    } else {
9386
9994
                        async_error(desc, err);
 
9995
                    }
 
9996
#else
 
9997
                    async_error(desc, err);
9387
9998
#endif
9388
9999
                    driver_cancel_timer(desc->port);
9389
10000
                    sock_select(desc,FD_READ,0);
9481
10092
            int code = sock_peer(desc->s,
9482
10093
                                 (struct sockaddr*) &desc->remote, &sz);
9483
10094
 
9484
 
            if (code == SOCKET_ERROR) {
 
10095
            if (IS_SOCKET_ERROR(code)) {
9485
10096
                desc->state = PACKET_STATE_BOUND;  /* restore state */
9486
10097
                ret =  async_error(desc, sock_errno());
9487
10098
                goto done;
9922
10533
    if (!inet_set_address(AF_INET, &addr, buf, &blen))
9923
10534
        return 0;
9924
10535
 
9925
 
    if (SOCKET_ERROR == sock_connect(s,
 
10536
    if (IS_SOCKET_ERROR(sock_connect(s,
9926
10537
                                     (struct sockaddr *) &addr,
9927
 
                                     sizeof(struct sockaddr_in)))
 
10538
                                     sizeof(struct sockaddr_in))))
9928
10539
        return 0;
9929
10540
    return 1;
9930
10541
}
9931
10542
 
9932
10543
Sint erts_sock_send(erts_sock_t socket, const void *buf, Sint len)
9933
10544
{
9934
 
    return (Sint) sock_send((SOCKET) socket, buf, (size_t) len, 0);
 
10545
    Sint result = (Sint) sock_send((SOCKET) socket, buf, (size_t) len, 0);
 
10546
    if (IS_SOCKET_ERROR(result))
 
10547
        return SOCKET_ERROR;
 
10548
    return result;
9935
10549
}
9936
10550
 
9937
10551
 
9938
10552
int erts_sock_gethostname(char *buf, int bufsz)
9939
10553
{
9940
 
    if (sock_hostname(buf, bufsz) == SOCKET_ERROR)
9941
 
        return -1;
 
10554
    if (IS_SOCKET_ERROR(sock_hostname(buf, bufsz)))
 
10555
        return SOCKET_ERROR;
9942
10556
    return 0;
9943
10557
}
9944
10558