~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/ssl/c_src/esock.c

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
63
63
 *
64
64
 * Every SELECT_TIMEOUT second we try to write to those file
65
65
 * descriptors that have non-empty wq's (the only way to detect that a
66
 
 * far end has gone away is to write to it). XXX True?
 
66
 * far end has gone away is to write to it).
67
67
 *
68
68
 * STATE TRANSITIONS
69
69
 *
96
96
 * A connection in state SSL_ACCEPT can be closed and removed without
97
97
 * synchronization.
98
98
 *
99
 
 * XXX We should ONLY consider the the states of fd and proxy->fd, and
100
 
 * neither rely on any control information received regarding their
101
 
 * desired states, nor send any control information about their actual
102
 
 * states. In particular, FROMNET_CLOSE should never be sent.
103
 
 *
104
 
 * XXX If we do not go through the JOINED state, we may leak proxy
105
 
 * file descriptors. It is when a connection is in the state CONNECTED
106
 
 * that a proxy file descriptor is created. It is ssl_broker.erl that
107
 
 * makes the connect. It knows cp->fd, and the port number of its own
108
 
 * socket.  It is however only if the broker crashes (or gets killed)
109
 
 * that we lose a descriptor.  */
110
 
 
 
99
 */
 
100
#ifdef HAVE_CONFIG_H
 
101
#include "config.h"
 
102
#endif
111
103
#ifdef __WIN32__
112
104
#include "esock_winsock.h"
113
105
#endif
144
136
#include "esock_ssl.h"
145
137
#include "esock_osio.h"
146
138
#include "esock_posix_str.h"
 
139
#include "esock_poll.h"
147
140
 
148
141
#define MAJOR_VERSION   2
149
142
#define MINOR_VERSION   0
150
143
#define MAXREPLYBUF     256
151
 
#define RWBUFLEN        4096
 
144
#define RWBUFLEN        (32*1024)
152
145
#define IS_CLIENT       0
153
146
#define IS_SERVER       1
154
147
#define SELECT_TIMEOUT  2       /* seconds */
165
158
#define JOINED_STATE_INVALID(cp) (!(PROXY_TO_SSL_VALID(cp)) && \
166
159
                                !(SSL_TO_PROXY_VALID(cp)))
167
160
static int loop(void);
 
161
static int set_poll_conns(Connection *cp, EsockPoll *ep, int verbose);
 
162
static Connection *next_polled_conn(Connection *cp, Connection **cpnext,
 
163
                                    EsockPoll *ep, int set_wq_fds);
 
164
 
168
165
static void leave_joined_state(Connection *cp);
169
166
static void do_shutdown(Connection *cp);
170
167
static void close_and_remove_connection(Connection *cp);
174
171
static int get_pars(unsigned char *buf, char *fmt, va_list args);
175
172
static FD do_connect(char *lipstring, int lport, char *fipstring, int fport);
176
173
static FD do_listen(char *ipstring, int lport, int backlog, int *aport);
 
174
static FD do_accept(FD listensock, struct sockaddr *saddr, int *len);
177
175
static void print_connections(void);
 
176
static int check_num_sock_fds(FD fd); 
178
177
static void safe_close(FD fd);
179
178
static Connection *new_connection(int state, FD fd);
180
179
static Connection *get_connection(FD fd);
186
185
static void clean_up(void);
187
186
 
188
187
static Connection  *connections = NULL;
189
 
static fd_set readmask, writemask, exceptmask;
 
188
static int num_sock_fds;        /* On UNIX all file descriptors */
190
189
static Proxy *proxies = NULL;
191
190
static int proxy_listensock = INVALID_FD;
192
191
static int proxy_listenport = 0;
193
 
static int proxy_backlog = 5;
 
192
static int proxy_backlog = 128;
194
193
static int proxysock_last_err = 0;
195
194
static int proxysock_err_cnt = 0;
196
195
static char rwbuf[RWBUFLEN];
197
196
static unsigned char *ebuf = NULL; /* Set by read_ctrl() */
198
 
static unsigned long one = 1;
199
 
static struct timeval timeout = {SELECT_TIMEOUT, 0};
200
197
 
201
198
static char *connstr[] = {
202
199
    "STATE_NONE", 
230
227
 
231
228
    set_binary_mode();
232
229
    setvbuf(stderr, NULL, _IONBF, 0);
 
230
    /* Two sockets for the stdin socket pipe (local thread). */
 
231
    num_sock_fds = 2;           
233
232
#else
234
233
    pid_t pid;
 
234
    num_sock_fds = 3;           /* 0, 1, 2 */
235
235
#endif
236
236
 
237
237
    pid = getpid();
251
251
            i++;
252
252
            proxy_backlog = atoi(argv[i]);
253
253
            i++;
 
254
        } else if (strcmp(argv[i], "-pv") == 0) {
 
255
            i++;
 
256
            protocol_version = atoi(argv[i]);
 
257
            i++;
254
258
        } else if (strcmp(argv[i], "-dd") == 0) {
255
259
            i++;
256
260
            logfile = esock_malloc(strlen(argv[i]) + 64);
266
270
    }
267
271
    if (debug || debugmsg) {
268
272
        DEBUGF(("Starting ssl_esock\n"));
269
 
        if (logfile) open_ssllog(logfile);
 
273
        if (logfile) {
 
274
            open_ssllog(logfile);
 
275
#ifndef __WIN32__
 
276
            num_sock_fds++;
 
277
#endif
 
278
        }
270
279
        atexit(close_ssllog);
271
280
        DEBUGF(("pid = %d\n", getpid()));
272
281
    }
308
317
#endif
309
318
 
310
319
    /* Create the local proxy listen socket and set it to non-blocking */
311
 
    /* XXX Check backlog */
312
320
    proxy_listensock = do_listen("127.0.0.1", proxy_listenport, 
313
321
                                 proxy_backlog, &proxy_listenport);
314
322
    if (proxy_listensock == INVALID_FD) {
345
353
 
346
354
static int loop(void)
347
355
{
 
356
    EsockPoll pollfd;
348
357
    FD fd, msgsock, listensock, connectsock, proxysock;
349
358
    int cc, wc, fport, lport, pport, length, backlog, intref, op;
350
359
    int value;
351
360
    char *lipstring, *fipstring;
352
361
    char *flags;
 
362
    char *protocol_vsn, *cipher;
353
363
    unsigned char *cert, *bin;
354
364
    int certlen, binlen;
355
365
    struct sockaddr_in iserv_addr;
356
 
    int sret = 1, j;
 
366
    int sret = 1;
357
367
    Connection *cp, *cpnext, *newcp;
358
368
    Proxy *pp;
359
 
    struct timeval tv;
360
369
    time_t last_time = 0, now = 0;
361
370
    int set_wq_fds;
362
371
 
 
372
    esock_poll_init(&pollfd);
 
373
 
363
374
    while(1) {
 
375
        esock_poll_zero(&pollfd);
 
376
        esock_poll_fd_set_read(&pollfd, proxy_listensock);
 
377
        esock_poll_fd_set_read(&pollfd, local_read_fd);
364
378
 
365
 
        FD_ZERO(&readmask);
366
 
        FD_ZERO(&writemask);
367
 
        FD_ZERO(&exceptmask);
368
 
        FD_SET(local_read_fd, &readmask);
369
 
        FD_SET(proxy_listensock, &readmask);
370
 
        tv = timeout;           /* select() might change tv */
371
379
        set_wq_fds = 0;
372
380
 
373
381
        if (sret)               /* sret == 1 the first time. */
374
382
            DEBUGF(("==========LOOP=============\n"));
375
383
 
376
 
        cc = esock_ssl_set_masks(connections, &readmask, &writemask, 
377
 
                                 &exceptmask, sret) + 1;
 
384
        cc = set_poll_conns(connections, &pollfd, sret) + 1;
 
385
 
378
386
        if (sret) {
379
387
            print_connections();
380
 
            DEBUGF(("Before select: %d descriptor%s\n", cc, 
381
 
                    (cc == 1) ? "" : "s"));
 
388
            DEBUGF(("Before poll/select: %d descriptor%s (total %d)\n",
 
389
                    cc, (cc == 1) ? "" : "s", num_sock_fds));
382
390
        }
383
391
 
384
 
        sret = select(FD_SETSIZE, &readmask, &writemask, &exceptmask, &tv);
 
392
        sret = esock_poll(&pollfd, SELECT_TIMEOUT);
385
393
        if (sret < 0) {
386
 
            DEBUGF(("select error: %s\n", psx_errstr()));
 
394
            DEBUGF(("select/poll error: %s\n", psx_errstr()));
387
395
            continue;
388
 
        } else if (sret == 0) {
389
 
            FD_ZERO(&readmask);
390
 
            FD_ZERO(&writemask);
391
 
            FD_ZERO(&exceptmask);
392
 
        }
393
 
 
394
 
        if (sret) {
395
 
            DEBUGF(("After select: %d descriptor%s: ", sret, 
396
 
                    (sret == 1) ? "" : "s"));
397
 
#ifndef __WIN32__
398
 
            for (j = 0; j < FD_SETSIZE; j++) {
399
 
                if (FD_ISSET(j, &readmask) || 
400
 
                    FD_ISSET(j, &writemask) ||
401
 
                    FD_ISSET(j, &exceptmask))
402
 
                    DEBUGF(("%d ", j));
403
 
            }
404
 
#else
405
 
            /* XXX Make this better */
406
 
            DEBUGF(("(not shown)"));
407
 
#endif
408
 
            DEBUGF(("\n"));
409
396
        }
410
397
        
411
398
        time(&now);
419
406
         * is later used as a reference for joining a proxy 
420
407
         * connection with a network connection.
421
408
         */
422
 
        if (FD_ISSET(proxy_listensock, &readmask)) {
 
409
 
 
410
        if (esock_poll_fd_isset_read(&pollfd, proxy_listensock)) {
423
411
            while (1) {
424
412
                length = sizeof(iserv_addr);
425
 
                proxysock = accept(proxy_listensock, 
426
 
                                   (struct sockaddr *)&iserv_addr, 
427
 
                                   (int*)&length);
 
413
                proxysock = do_accept(proxy_listensock, 
 
414
                                      (struct sockaddr *)&iserv_addr, 
 
415
                                      (int*)&length);
428
416
                if(proxysock == INVALID_FD) {
429
417
                    if (sock_errno() != ERRNO_BLOCK) {
430
 
                        /* XXX Here we have a major flaw. We can here
431
 
                         * for example get the error EMFILE, i.e. no
432
 
                         * more file descriptor available, but we do
433
 
                         * not have any specific connection to report
434
 
                         * the error to. 
435
 
                         * We increment the error counter and saves the
436
 
                         * last err.
 
418
                        /* We can here for example get the error
 
419
                         * EMFILE, i.e. no more file descriptors
 
420
                         * available, but we do not have any specific
 
421
                         * connection to report the error to.  We
 
422
                         * increment the error counter and saves the
 
423
                         * last err.  
437
424
                         */
438
425
                        proxysock_err_cnt++;
439
426
                        proxysock_last_err = sock_errno();
450
437
                        safe_close(proxysock);
451
438
                    } else {
452
439
                        /* Add to pending proxy connections */
 
440
                        SET_NONBLOCKING(proxysock);
453
441
                        pp = new_proxy(proxysock);
454
442
                        pp->peer_port = ntohs(iserv_addr.sin_port);
455
443
                        DEBUGF(("-----------------------------------\n"));
464
452
        /* 
465
453
         * Read control messages from Erlang
466
454
         */
467
 
        if (FD_ISSET(local_read_fd, &readmask)) {  
468
 
 
 
455
        if (esock_poll_fd_isset_read(&pollfd, local_read_fd)) {  
469
456
            cc = read_ctrl(&ebuf);
470
457
            if ( cc < 0 ) {
471
458
                DEBUGF(("Read loop -1 or 0\n"));
539
526
                    }
540
527
                    break;
541
528
 
 
529
                case ESOCK_GETCONNINFO_CMD:
 
530
                    /* 
 
531
                     * ebuf = {cmd(1), fd(4)}
 
532
                     */
 
533
                    input("4", &fd);
 
534
                    DEBUGF(("[GETCONNINFO_CMD] fd = %d\n", fd)); 
 
535
                    cp = get_connection(fd);
 
536
                    if (!cp) {
 
537
                        sock_set_errno(ERRNO_NOTSOCK);
 
538
                        reply(ESOCK_GETCONNINFO_ERR, "4s", fd, psx_errstr());
 
539
                    } else {
 
540
                        if (esock_ssl_getprotocol_version(cp,
 
541
                                                          &protocol_vsn) < 0)
 
542
                            reply(ESOCK_GETCONNINFO_ERR, "4s", fd, psx_errstr());
 
543
                        else if (esock_ssl_getcipher(cp, &cipher) < 0)
 
544
                            reply(ESOCK_GETCONNINFO_ERR, "4s", fd, psx_errstr());
 
545
                        else
 
546
                        /*
 
547
                         * reply  = {cmd(1), fd(4), protocol(N), 0(1),
 
548
                         *          cipher(N), 0(1)}
 
549
                         */
 
550
                            reply(ESOCK_GETCONNINFO_REP, "4ss", fd, 
 
551
                                  protocol_vsn, cipher);
 
552
                    }
 
553
                    break;
 
554
 
542
555
                case ESOCK_GETPEERCERT_CMD:
543
556
                    /* 
544
557
                     * ebuf = {cmd(1), fd(4)}
613
626
                            cp->proxy->bp = 1;
614
627
                        switch (cp->state) {
615
628
                        case ESOCK_JOINED:
 
629
                            cp->close = 1;
 
630
                            if (JOINED_STATE_INVALID(cp))
 
631
                                leave_joined_state(cp);
 
632
                            break;
616
633
                        case ESOCK_SSL_SHUTDOWN:
 
634
                            cp->close = 1;
617
635
                            DEBUGF(("  close flag set\n"));
618
 
                            cp->close = 1;
619
636
                            break;
620
637
                        default:
621
638
                            DEBUGF(("-> (removal)\n"));
622
639
                            close_and_remove_connection(cp);
623
640
                        }
624
641
                    } else 
625
 
                        DEBUGF(("%s[ERLANG_CLOSE]: ERROR: fd = %d not found\n",
 
642
                        DEBUGF(("%s[CLOSE_CMD]: ERROR: fd = %d not found\n",
626
643
                                connstr[cp->state], fd));
627
644
                    break;
628
645
 
789
806
        /* Note: We may remove the current connection (cp). Thus we
790
807
         * must be careful not to read cp->next after cp has been
791
808
         * removed.  */
792
 
        for (cp = esock_ssl_read_masks(connections, &cpnext, &readmask, 
793
 
                                       &writemask, &exceptmask, set_wq_fds); 
 
809
        for (cp = next_polled_conn(connections, &cpnext, &pollfd, set_wq_fds); 
794
810
             cp != NULL; 
795
 
             cp = esock_ssl_read_masks(cpnext, &cpnext, &readmask, 
796
 
                                       &writemask, &exceptmask, set_wq_fds)
797
 
            ) {
 
811
             cp = next_polled_conn(cpnext, &cpnext, &pollfd, set_wq_fds)
 
812
             ) {
798
813
 
799
814
            switch(cp->state) {
800
815
 
810
825
                DEBUGF(("ACTIVE_LISTENING - trying to accept on %d\n", 
811
826
                       cp->fd));
812
827
                length = sizeof(iserv_addr);
813
 
                msgsock = accept(cp->fd, (struct sockaddr*)&iserv_addr, 
814
 
                                 (int*)&length);
 
828
                msgsock = do_accept(cp->fd, (struct sockaddr*)&iserv_addr, 
 
829
                                    (int*)&length);
815
830
                if(msgsock == INVALID_FD)  {
816
831
                    DEBUGF(("accept error: %s\n", psx_errstr()));
817
832
                    reply(ESOCK_ACCEPT_ERR, "4s", cp->fd, psx_errstr());
859
874
                    /* SSL handshake successful: publish */
860
875
                    reply(ESOCK_ACCEPT_REP, "44", cp->listen_fd, msgsock);
861
876
                    DEBUGF(("-> CONNECTED\n"));
 
877
                    DEBUGF((" Session was %sreused.\n", 
 
878
                            (esock_ssl_session_reused(cp)) ? "" : "NOT "));
862
879
                    cp->state = ESOCK_CONNECTED;
863
880
                }
864
881
                break;
875
892
                /* 
876
893
                 * Reading from Proxy, writing to SSL 
877
894
                 */
878
 
                if (FD_ISSET(cp->fd, &writemask)) {
 
895
                if (esock_poll_fd_isset_write(&pollfd, cp->fd)) {
879
896
                    /* If there is a write queue, write to ssl only */
880
897
                    if (cp->wq.len > 0) { 
881
898
                        /* The write retry semantics of SSL_write in
929
946
                                cp->wq.len = 0;
930
947
                        }
931
948
                    }
932
 
                } else if (FD_ISSET(cp->proxy->fd, &readmask)) {
 
949
                } else if (esock_poll_fd_isset_read(&pollfd, cp->proxy->fd)) {
933
950
                    /* Read from proxy and write to SSL */
934
951
                    DEBUGF(("-----------------------------------\n"));
935
952
                    DEBUGF(("JOINED: reading from proxy, "
980
997
                            cp->wq.len = cc - wc;
981
998
                            cp->wq.offset = 0;
982
999
                        } 
983
 
                    } else if (cc == 0) {
984
 
                        /* EOF proxy */
985
 
                        DEBUGF(("proxy eof\n"));
 
1000
                    } else {
 
1001
                        /* EOF proxy or error */
 
1002
                        DEBUGF(("proxy eof or error\n"));
986
1003
                        cp->proxy->eof = 1;
987
1004
                        if (cp->wq.len == 0) {
988
1005
                            esock_ssl_shutdown(cp);
992
1009
                            leave_joined_state(cp);
993
1010
                            break;
994
1011
                        }
995
 
                    } else {
996
 
                        /* This should not happen */
997
 
                        DEBUGF(("ERROR: proxy readmask set, cc < 0,  fd = %d"
998
 
                               " proxyfd = %d\n", cp->fd, cp->proxy->fd));
999
1012
                    }
1000
1013
                }
1001
1014
                /* 
1002
1015
                 * Reading from SSL, writing to proxy 
1003
1016
                 */
1004
 
                if (FD_ISSET(cp->proxy->fd, &writemask)) {
 
1017
                if (esock_poll_fd_isset_write(&pollfd, cp->proxy->fd)) {
1005
1018
                    /* If there is a write queue, write to proxy only */
1006
1019
                    if (cp->proxy->wq.len > 0) {
1007
1020
                        DEBUGF(("-----------------------------------\n"));
1031
1044
                                cp->proxy->wq.len = 0;
1032
1045
                        }
1033
1046
                    }
1034
 
                } else if (FD_ISSET(cp->fd, &readmask)) {
 
1047
                } else if (esock_poll_fd_isset_read(&pollfd, cp->fd)) {
1035
1048
                    /* Read from SSL and write to proxy */
1036
1049
                    DEBUGF(("-----------------------------------\n"));
1037
1050
                    DEBUGF(("JOINED: read from ssl fd = %d\n",
1115
1128
                length = sizeof(iserv_addr);
1116
1129
                if (
1117
1130
#ifdef __WIN32__
1118
 
                    FD_ISSET(connectsock, &exceptmask)
 
1131
                    esock_poll_fd_isset_exception(&pollfd, connectsock)
1119
1132
#else
1120
1133
                    getpeername(connectsock, (struct sockaddr *)&iserv_addr, 
1121
1134
                                &length) < 0
1166
1179
   }
1167
1180
}
1168
1181
 
 
1182
static int set_poll_conns(Connection *cp, EsockPoll *ep, int verbose)
 
1183
{
 
1184
    int i = 0;
 
1185
    
 
1186
    if (verbose)
 
1187
        DEBUGF(("MASKS SET FOR FD: "));
 
1188
    while (cp) {
 
1189
        switch (cp->state) {
 
1190
        case ESOCK_ACTIVE_LISTENING:
 
1191
            if (verbose)
 
1192
                DEBUGF(("%d (read) ", cp->fd));
 
1193
            esock_poll_fd_set_read(ep, cp->fd);
 
1194
            break;
 
1195
        case ESOCK_WAIT_CONNECT:
 
1196
            if (verbose)
 
1197
                DEBUGF(("%d (write) ", cp->fd));
 
1198
            esock_poll_fd_set_write(ep, cp->fd);
 
1199
#ifdef __WIN32__
 
1200
            esock_poll_fd_set_exception(ep, cp->fd); /* Failure shows in exceptions */
 
1201
#endif
 
1202
            break;
 
1203
        case ESOCK_SSL_CONNECT:
 
1204
        case ESOCK_SSL_ACCEPT:
 
1205
            if (cp->ssl_want == ESOCK_SSL_WANT_READ) {
 
1206
                if (verbose)
 
1207
                    DEBUGF(("%d (read) ", cp->fd));
 
1208
                esock_poll_fd_set_read(ep, cp->fd);
 
1209
            } else if (cp->ssl_want == ESOCK_SSL_WANT_WRITE) {
 
1210
                if (verbose)
 
1211
                    DEBUGF(("%d (write) ", cp->fd));
 
1212
                esock_poll_fd_set_write(ep, cp->fd);
 
1213
            }
 
1214
            break;
 
1215
        case ESOCK_JOINED:
 
1216
            if (!cp->bp) {
 
1217
                if (cp->wq.len) {
 
1218
                    if (verbose)
 
1219
                        DEBUGF(("%d (write) ", cp->fd));
 
1220
                    esock_poll_fd_set_write(ep, cp->fd);
 
1221
                } else if (!cp->proxy->eof) {
 
1222
                    if (verbose)
 
1223
                        DEBUGF(("%d (read) ", cp->proxy->fd));
 
1224
                    esock_poll_fd_set_read(ep, cp->proxy->fd);
 
1225
                }
 
1226
            }
 
1227
            if (!cp->proxy->bp) {
 
1228
                if (cp->proxy->wq.len) {
 
1229
                    if (verbose)
 
1230
                        DEBUGF(("%d (write) ", cp->proxy->fd));
 
1231
                    esock_poll_fd_set_write(ep, cp->proxy->fd);
 
1232
                } else if (!cp->eof) {
 
1233
                    if (verbose)
 
1234
                        DEBUGF(("%d (read) ", cp->fd));
 
1235
                    esock_poll_fd_set_read(ep, cp->fd);
 
1236
                }
 
1237
            }
 
1238
            break;
 
1239
        case ESOCK_SSL_SHUTDOWN:
 
1240
            if (cp->ssl_want == ESOCK_SSL_WANT_READ) {
 
1241
                if (verbose)
 
1242
                    DEBUGF(("%d (read) ", cp->fd));
 
1243
                esock_poll_fd_set_read(ep, cp->fd);
 
1244
            } else if (cp->ssl_want == ESOCK_SSL_WANT_WRITE) {
 
1245
                if (verbose)
 
1246
                    DEBUGF(("%d (write) ", cp->fd));
 
1247
                esock_poll_fd_set_write(ep, cp->fd);
 
1248
            }
 
1249
            break;
 
1250
        default:
 
1251
            break;
 
1252
        }
 
1253
        i++;
 
1254
        cp = cp->next;
 
1255
    }
 
1256
    if (verbose)
 
1257
        DEBUGF(("\n"));
 
1258
    return i;
 
1259
}
 
1260
 
 
1261
 
 
1262
static Connection *next_polled_conn(Connection *cp, Connection **cpnext,
 
1263
                                    EsockPoll *ep, int set_wq_fds)
 
1264
{
 
1265
    while(cp) {
 
1266
        if (esock_poll_fd_isset_read(ep, cp->fd) ||
 
1267
            (cp->proxy && esock_poll_fd_isset_read(ep, cp->proxy->fd)) ||
 
1268
            (esock_poll_fd_isset_write(ep, cp->fd)) ||
 
1269
            (cp->proxy && esock_poll_fd_isset_write(ep, cp->proxy->fd))
 
1270
#ifdef __WIN32__
 
1271
            || esock_poll_fd_isset_exception(ep, cp->fd) /* Connect failure in WIN32 */
 
1272
#endif
 
1273
            || (set_wq_fds && (cp->wq.len || 
 
1274
                               (cp->proxy && cp->proxy->wq.len)))) {
 
1275
            *cpnext = cp->next;
 
1276
            return cp;
 
1277
        }
 
1278
        cp = cp->next;
 
1279
    }
 
1280
    *cpnext = NULL;
 
1281
    return NULL;
 
1282
}
 
1283
 
1169
1284
static void leave_joined_state(Connection *cp)
1170
1285
{
1171
1286
    shutdown(cp->proxy->fd, SHUTDOWN_ALL);
1367
1482
    long inaddr;
1368
1483
    FD fd;
1369
1484
   
1370
 
    if((fd = socket(AF_INET, SOCK_STREAM, 0)) == INVALID_FD) {
 
1485
    if ((fd = socket(AF_INET, SOCK_STREAM, 0)) == INVALID_FD) {
1371
1486
        DEBUGF(("Error calling socket()\n"));
1372
1487
        return fd;
1373
1488
    }
 
1489
    if (check_num_sock_fds(fd) < 0) 
 
1490
        return INVALID_FD;
1374
1491
    DEBUGF(("  fd = %d\n", fd));
1375
1492
 
1376
1493
    /* local */
1418
1535
 
1419
1536
static FD do_listen(char *ipstring, int lport, int backlog, int *aport)
1420
1537
{
 
1538
    static int one = 1;         /* Type must be int, not long */
1421
1539
    struct sockaddr_in sock_addr;
1422
1540
    long inaddr;
1423
1541
    int length;
1424
1542
    FD fd;
1425
1543
    
1426
 
    if((fd = socket(AF_INET, SOCK_STREAM, 0)) == INVALID_FD) {
 
1544
    if ((fd = socket(AF_INET, SOCK_STREAM, 0)) == INVALID_FD) {
1427
1545
        DEBUGF(("Error calling socket()\n"));
1428
1546
        return fd;
1429
1547
    }
 
1548
    if (check_num_sock_fds(fd) < 0) 
 
1549
        return INVALID_FD;
1430
1550
    DEBUGF(("  fd = %d\n", fd));
1431
1551
    if ((inaddr = inet_addr(ipstring)) == INADDR_NONE) {
1432
1552
        DEBUGF(("Error in inet_addr(): ipstring = %s\n", ipstring));
1463
1583
    return fd;
1464
1584
}
1465
1585
 
 
1586
static FD do_accept(FD listensock, struct sockaddr *saddr, int *len)
 
1587
{
 
1588
    FD fd;
 
1589
 
 
1590
    if ((fd = accept(listensock, saddr, len)) == INVALID_FD) {
 
1591
        DEBUGF(("Error calling accept()\n"));
 
1592
        return fd;
 
1593
    }
 
1594
    if (check_num_sock_fds(fd) < 0) 
 
1595
        return INVALID_FD;
 
1596
    return fd;
 
1597
}
1466
1598
 
1467
1599
static Connection *new_connection(int state, FD fd)
1468
1600
{
1479
1611
    cp->ssl_want = 0;
1480
1612
    cp->eof = 0;
1481
1613
    cp->bp = 0;
1482
 
    cp->clean = 0;
 
1614
    cp->clean = 0;              /* XXX Used? */
1483
1615
    cp->close = 0;
1484
1616
    cp->origin = -1;
1485
1617
    cp->flags = NULL;
1550
1682
            DEBUGF(("remove_connection: fd = %d\n", cp->fd));
1551
1683
            esock_ssl_free(cp); /* frees cp->opaque only */
1552
1684
            esock_free(cp->flags);
1553
 
            closelog(cp->logfp);
 
1685
            closelog(cp->logfp); /* XXX num_sock_fds */
1554
1686
            esock_free(cp->wq.buf);
1555
1687
            if (cp->proxy) {
1556
1688
                safe_close(cp->proxy->fd);
1615
1747
    }
1616
1748
}
1617
1749
 
 
1750
static int check_num_sock_fds(FD fd) 
 
1751
{
 
1752
    num_sock_fds++;             /* fd is valid */
 
1753
#ifdef USE_SELECT
 
1754
    if (num_sock_fds > FD_SETSIZE) {
 
1755
        num_sock_fds--;
 
1756
        sock_set_errno(ERRNO_MFILE);
 
1757
        safe_close(fd);
 
1758
        return -1;
 
1759
    }
 
1760
#endif
 
1761
    return 0;
 
1762
}
 
1763
 
1618
1764
static void safe_close(FD fd)
1619
1765
{
1620
1766
    int err;
1622
1768
    err = sock_errno();
1623
1769
    DEBUGF(("safe_close fd = %d\n", fd));
1624
1770
    if (sock_close(fd) < 0) {
1625
 
        DEBUGF(("sock_close close failed\n"));
 
1771
        DEBUGF(("safe_close failed\n"));
 
1772
    } else {
 
1773
        num_sock_fds--;
1626
1774
    }
1627
1775
    sock_set_errno(err);
1628
1776
}