~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to erts/emulator/sys/unix/sys.c

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
/*
2
2
 * %CopyrightBegin%
3
3
 *
4
 
 * Copyright Ericsson AB 1996-2010. All Rights Reserved.
 
4
 * Copyright Ericsson AB 1996-2011. All Rights Reserved.
5
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
52
52
#define ERTS_WANT_GOT_SIGUSR1
53
53
#define WANT_NONBLOCKING    /* must define this to pull in defs from sys.h */
54
54
#include "sys.h"
 
55
#include "erl_thr_progress.h"
 
56
 
 
57
#if defined(__APPLE__) && defined(__MACH__) && !defined(__DARWIN__)
 
58
#define __DARWIN__ 1
 
59
#endif
 
60
 
55
61
 
56
62
#ifdef USE_THREADS
57
63
#include "erl_threads.h"
122
128
static ErtsSysReportExit *report_exit_transit_list;
123
129
#endif
124
130
 
125
 
extern int  check_async_ready(void);
126
131
extern int  driver_interrupt(int, int);
127
132
extern void do_break(void);
128
133
 
160
165
#endif
161
166
 
162
167
#ifdef ERTS_SMP
163
 
erts_smp_atomic_t erts_got_sigusr1;
 
168
erts_smp_atomic32_t erts_got_sigusr1;
164
169
#define ERTS_SET_GOT_SIGUSR1 \
165
 
  erts_smp_atomic_set(&erts_got_sigusr1, 1)
 
170
  erts_smp_atomic32_set_mb(&erts_got_sigusr1, 1)
166
171
#define ERTS_UNSET_GOT_SIGUSR1 \
167
 
  erts_smp_atomic_set(&erts_got_sigusr1, 0)
168
 
static erts_smp_atomic_t have_prepared_crash_dump;
 
172
  erts_smp_atomic32_set_mb(&erts_got_sigusr1, 0)
 
173
static erts_smp_atomic32_t have_prepared_crash_dump;
169
174
#define ERTS_PREPARED_CRASH_DUMP \
170
 
  ((int) erts_smp_atomic_xchg(&have_prepared_crash_dump, 1))
 
175
  ((int) erts_smp_atomic32_xchg_nob(&have_prepared_crash_dump, 1))
171
176
#else
172
177
volatile int erts_got_sigusr1;
173
178
#define ERTS_SET_GOT_SIGUSR1 (erts_got_sigusr1 = 1)
235
240
 * a few variables used by the break handler 
236
241
 */
237
242
#ifdef ERTS_SMP
238
 
erts_smp_atomic_t erts_break_requested;
 
243
erts_smp_atomic32_t erts_break_requested;
239
244
#define ERTS_SET_BREAK_REQUESTED \
240
 
  erts_smp_atomic_set(&erts_break_requested, (long) 1)
 
245
  erts_smp_atomic32_set_nob(&erts_break_requested, (erts_aint32_t) 1)
241
246
#define ERTS_UNSET_BREAK_REQUESTED \
242
 
  erts_smp_atomic_set(&erts_break_requested, (long) 0)
 
247
  erts_smp_atomic32_set_nob(&erts_break_requested, (erts_aint32_t) 0)
243
248
#else
244
249
volatile int erts_break_requested = 0;
245
250
#define ERTS_SET_BREAK_REQUESTED (erts_break_requested = 1)
258
263
struct {
259
264
    int (*select)(ErlDrvPort, ErlDrvEvent, int, int);
260
265
    int (*event)(ErlDrvPort, ErlDrvEvent, ErlDrvEventData);
 
266
    void (*check_io_as_interrupt)(void);
261
267
    void (*check_io_interrupt)(int);
262
 
    void (*check_io_interrupt_tmd)(int, long);
 
268
    void (*check_io_interrupt_tmd)(int, erts_short_time_t);
263
269
    void (*check_io)(int);
264
270
    Uint (*size)(void);
265
271
    Eterm (*info)(void *);
297
303
    if (erts_use_kernel_poll) {
298
304
        io_func.select                  = driver_select_kp;
299
305
        io_func.event                   = driver_event_kp;
 
306
#ifdef ERTS_POLL_NEED_ASYNC_INTERRUPT_SUPPORT
 
307
        io_func.check_io_as_interrupt   = erts_check_io_async_sig_interrupt_kp;
 
308
#endif
300
309
        io_func.check_io_interrupt      = erts_check_io_interrupt_kp;
301
310
        io_func.check_io_interrupt_tmd  = erts_check_io_interrupt_timed_kp;
302
311
        io_func.check_io                = erts_check_io_kp;
309
318
    else {
310
319
        io_func.select                  = driver_select_nkp;
311
320
        io_func.event                   = driver_event_nkp;
 
321
#ifdef ERTS_POLL_NEED_ASYNC_INTERRUPT_SUPPORT
 
322
        io_func.check_io_as_interrupt   = erts_check_io_async_sig_interrupt_nkp;
 
323
#endif
312
324
        io_func.check_io_interrupt      = erts_check_io_interrupt_nkp;
313
325
        io_func.check_io_interrupt_tmd  = erts_check_io_interrupt_timed_nkp;
314
326
        io_func.check_io                = erts_check_io_nkp;
320
332
    }
321
333
}
322
334
 
 
335
#ifdef ERTS_POLL_NEED_ASYNC_INTERRUPT_SUPPORT
 
336
#define ERTS_CHK_IO_AS_INTR()   (*io_func.check_io_as_interrupt)()
 
337
#else
 
338
#define ERTS_CHK_IO_AS_INTR()   (*io_func.check_io_interrupt)(1)
 
339
#endif
323
340
#define ERTS_CHK_IO_INTR        (*io_func.check_io_interrupt)
324
341
#define ERTS_CHK_IO_INTR_TMD    (*io_func.check_io_interrupt_tmd)
325
342
#define ERTS_CHK_IO             (*io_func.check_io)
334
351
    max_files = erts_check_io_max_files();
335
352
}
336
353
 
 
354
#ifdef ERTS_POLL_NEED_ASYNC_INTERRUPT_SUPPORT
 
355
#define ERTS_CHK_IO_AS_INTR()   erts_check_io_async_sig_interrupt()
 
356
#else
 
357
#define ERTS_CHK_IO_AS_INTR()   erts_check_io_interrupt(1)
 
358
#endif
337
359
#define ERTS_CHK_IO_INTR        erts_check_io_interrupt
338
360
#define ERTS_CHK_IO_INTR_TMD    erts_check_io_interrupt_timed
339
361
#define ERTS_CHK_IO             erts_check_io
341
363
 
342
364
#endif
343
365
 
344
 
#ifdef ERTS_SMP
345
366
void
346
367
erts_sys_schedule_interrupt(int set)
347
368
{
348
369
    ERTS_CHK_IO_INTR(set);
349
370
}
350
371
 
 
372
#ifdef ERTS_SMP
351
373
void
352
 
erts_sys_schedule_interrupt_timed(int set, long msec)
 
374
erts_sys_schedule_interrupt_timed(int set, erts_short_time_t msec)
353
375
{
354
376
    ERTS_CHK_IO_INTR_TMD(set, msec);
355
377
}
359
381
erts_sys_misc_mem_sz(void)
360
382
{
361
383
    Uint res = ERTS_CHK_IO_SZ();
362
 
    res += erts_smp_atomic_read(&sys_misc_mem_sz);
 
384
    res += erts_smp_atomic_read_mb(&sys_misc_mem_sz);
363
385
    return res;
364
386
}
365
387
 
504
526
#endif
505
527
    }
506
528
#ifdef ERTS_SMP
507
 
    erts_smp_atomic_init(&erts_break_requested, 0);
508
 
    erts_smp_atomic_init(&erts_got_sigusr1, 0);
509
 
    erts_smp_atomic_init(&have_prepared_crash_dump, 0);
 
529
    erts_smp_atomic32_init_nob(&erts_break_requested, 0);
 
530
    erts_smp_atomic32_init_nob(&erts_got_sigusr1, 0);
 
531
    erts_smp_atomic32_init_nob(&have_prepared_crash_dump, 0);
510
532
#else
511
533
    erts_break_requested = 0;
512
534
    erts_got_sigusr1 = 0;
516
538
    children_died = 0;
517
539
#endif
518
540
#endif /* USE_THREADS */
519
 
    erts_smp_atomic_init(&sys_misc_mem_sz, 0);
 
541
    erts_smp_atomic_init_nob(&sys_misc_mem_sz, 0);
520
542
}
521
543
 
522
544
void
523
545
erl_sys_init(void)
524
546
{
525
 
    erts_smp_rwmtx_init(&environ_rwmtx, "environ");
526
547
#if !DISABLE_VFORK
527
548
 {
528
549
    int res;
548
569
                   + sizeof(CHILD_SETUP_PROG_NAME)
549
570
                   + 1);
550
571
    child_setup_prog = erts_alloc(ERTS_ALC_T_CS_PROG_PATH, csp_path_sz);
551
 
    erts_smp_atomic_add(&sys_misc_mem_sz, csp_path_sz);
 
572
    erts_smp_atomic_add_nob(&sys_misc_mem_sz, csp_path_sz);
552
573
    sprintf(child_setup_prog,
553
574
            "%s%c%s",
554
575
            bindir,
727
748
      erl_exit(ERTS_INTR_EXIT, "");
728
749
 
729
750
  ERTS_SET_BREAK_REQUESTED;
730
 
  ERTS_CHK_IO_INTR(1); /* Make sure we don't sleep in poll */
 
751
  ERTS_CHK_IO_AS_INTR(); /* Make sure we don't sleep in poll */
731
752
}
732
753
 
733
754
/* set up signal handlers for break and quit */
927
948
os_flavor(char* namebuf,        /* Where to return the name. */
928
949
          unsigned size)        /* Size of name buffer. */
929
950
{
930
 
    static int called = 0;
931
 
    static struct utsname uts;  /* Information about the system. */
932
 
 
933
 
    if (!called) {
934
 
        char* s;
935
 
 
936
 
        (void) uname(&uts);
937
 
        called = 1;
938
 
        for (s = uts.sysname; *s; s++) {
939
 
            if (isupper((int) *s)) {
940
 
                *s = tolower((int) *s);
941
 
            }
 
951
    struct utsname uts;         /* Information about the system. */
 
952
    char* s;
 
953
 
 
954
    (void) uname(&uts);
 
955
    for (s = uts.sysname; *s; s++) {
 
956
        if (isupper((int) *s)) {
 
957
            *s = tolower((int) *s);
942
958
        }
943
959
    }
944
960
    strcpy(namebuf, uts.sysname);
1017
1033
/* Driver interfaces */
1018
1034
static ErlDrvData spawn_start(ErlDrvPort, char*, SysDriverOpts*);
1019
1035
static ErlDrvData fd_start(ErlDrvPort, char*, SysDriverOpts*);
1020
 
static int fd_control(ErlDrvData, unsigned int, char *, int, char **, int);
 
1036
static ErlDrvSSizeT fd_control(ErlDrvData, unsigned int, char *, ErlDrvSizeT,
 
1037
                               char **, ErlDrvSizeT);
1021
1038
static ErlDrvData vanilla_start(ErlDrvPort, char*, SysDriverOpts*);
1022
1039
static int spawn_init(void);
1023
1040
static void fd_stop(ErlDrvData);
1024
1041
static void stop(ErlDrvData);
1025
1042
static void ready_input(ErlDrvData, ErlDrvEvent);
1026
1043
static void ready_output(ErlDrvData, ErlDrvEvent);
1027
 
static void output(ErlDrvData, char*, int);
 
1044
static void output(ErlDrvData, char*, ErlDrvSizeT);
1028
1045
static void outputv(ErlDrvData, ErlIOVec*);
1029
1046
static void stop_select(ErlDrvEvent, void*);
1030
1047
 
1103
1120
    stop_select
1104
1121
};
1105
1122
 
1106
 
#if defined(USE_THREADS) && !defined(ERTS_SMP)
1107
 
static int  async_drv_init(void);
1108
 
static ErlDrvData async_drv_start(ErlDrvPort, char*, SysDriverOpts*);
1109
 
static void async_drv_stop(ErlDrvData);
1110
 
static void async_drv_input(ErlDrvData, ErlDrvEvent);
1111
 
 
1112
 
/* INTERNAL use only */
1113
 
 
1114
 
struct erl_drv_entry async_driver_entry = {
1115
 
    async_drv_init,
1116
 
    async_drv_start,
1117
 
    async_drv_stop,
1118
 
    NULL,
1119
 
    async_drv_input,
1120
 
    NULL,
1121
 
    "async",
1122
 
    NULL,
1123
 
    NULL,
1124
 
    NULL,
1125
 
    NULL,
1126
 
    NULL,
1127
 
    NULL
1128
 
};
1129
 
#endif
1130
 
 
1131
1123
/* Handle SIGCHLD signals. */
1132
1124
#if (defined(SIG_SIGSET) || defined(SIG_SIGNAL))
1133
1125
static RETSIGTYPE onchld(void)
1141
1133
    smp_sig_notify('C');
1142
1134
#else
1143
1135
    children_died = 1;
1144
 
    ERTS_CHK_IO_INTR(1); /* Make sure we don't sleep in poll */
 
1136
    ERTS_CHK_IO_AS_INTR(); /* Make sure we don't sleep in poll */
1145
1137
#endif
1146
1138
}
1147
1139
 
1211
1203
   sys_sigset(SIGPIPE, SIG_IGN); /* Ignore - we'll handle the write failure */
1212
1204
   driver_data = (struct driver_data *)
1213
1205
       erts_alloc(ERTS_ALC_T_DRV_TAB, max_files * sizeof(struct driver_data));
1214
 
   erts_smp_atomic_add(&sys_misc_mem_sz,
1215
 
                       max_files * sizeof(struct driver_data));
 
1206
   erts_smp_atomic_add_nob(&sys_misc_mem_sz,
 
1207
                           max_files * sizeof(struct driver_data));
1216
1208
 
1217
1209
   for (i = 0; i < max_files; i++)
1218
1210
      driver_data[i].pid = -1;
1735
1727
    return -1;
1736
1728
}
1737
1729
 
1738
 
static int fd_control(ErlDrvData drv_data,
1739
 
                      unsigned int command,
1740
 
                      char *buf, int len,
1741
 
                      char **rbuf, int rlen)
 
1730
static ErlDrvSSizeT fd_control(ErlDrvData drv_data,
 
1731
                               unsigned int command,
 
1732
                               char *buf, ErlDrvSizeT len,
 
1733
                               char **rbuf, ErlDrvSizeT rlen)
1742
1734
{
1743
1735
    int fd = (int)(long)drv_data;
1744
1736
    char resbuff[2*sizeof(Uint32)];
1920
1912
{
1921
1913
    if (fd_data[fd].sz > 0) {
1922
1914
        erts_free(ERTS_ALC_T_FD_ENTRY_BUF, (void *) fd_data[fd].buf);
1923
 
        ASSERT(erts_smp_atomic_read(&sys_misc_mem_sz) >= fd_data[fd].sz);
1924
 
        erts_smp_atomic_add(&sys_misc_mem_sz, -1*fd_data[fd].sz);
 
1915
        ASSERT(erts_smp_atomic_read_nob(&sys_misc_mem_sz) >= fd_data[fd].sz);
 
1916
        erts_smp_atomic_add_nob(&sys_misc_mem_sz, -1*fd_data[fd].sz);
1925
1917
    }
1926
1918
    fd_data[fd].buf = NULL;
1927
1919
    fd_data[fd].sz = 0;
2010
2002
    int ix = driver_data[fd].port_num;
2011
2003
    int pb = driver_data[fd].packet_bytes;
2012
2004
    int ofd = driver_data[fd].ofd;
2013
 
    int n;
2014
 
    int sz;
 
2005
    ssize_t n;
 
2006
    ErlDrvSizeT sz;
2015
2007
    char lb[4];
2016
2008
    char* lbp;
2017
 
    int len = ev->size;
 
2009
    ErlDrvSizeT len = ev->size;
2018
2010
 
2019
2011
    /* (len > ((unsigned long)-1 >> (4-pb)*8)) */
 
2012
    /*    if (pb >= 0 && (len & (((ErlDrvSizeT)1 << (pb*8))) - 1) != len) {*/
2020
2013
    if (((pb == 2) && (len > 0xffff)) || (pb == 1 && len > 0xff)) {
2021
2014
        driver_failure_posix(ix, EINVAL);
2022
2015
        return; /* -1; */
2023
2016
    }
2024
 
    put_int32(len, lb);
 
2017
    /* Handles 0 <= pb <= 4 only */
 
2018
    put_int32((Uint32) len, lb);
2025
2019
    lbp = lb + (4-pb);
2026
2020
 
2027
2021
    ev->iov[0].iov_base = lbp;
2052
2046
}
2053
2047
 
2054
2048
 
2055
 
static void output(ErlDrvData e, char* buf, int len)
 
2049
static void output(ErlDrvData e, char* buf, ErlDrvSizeT len)
2056
2050
{
2057
2051
    int fd = (int)(long)e;
2058
2052
    int ix = driver_data[fd].port_num;
2059
2053
    int pb = driver_data[fd].packet_bytes;
2060
2054
    int ofd = driver_data[fd].ofd;
2061
 
    int n;
2062
 
    int sz;
 
2055
    ssize_t n;
 
2056
    ErlDrvSizeT sz;
2063
2057
    char lb[4];
2064
2058
    char* lbp;
2065
2059
    struct iovec iv[2];
2256
2250
                        port_inp_failure(port_num, ready_fd, -1);
2257
2251
                    }
2258
2252
                    else {
2259
 
                        erts_smp_atomic_add(&sys_misc_mem_sz, h);
 
2253
                        erts_smp_atomic_add_nob(&sys_misc_mem_sz, h);
2260
2254
                        sys_memcpy(buf, cpos, bytes_left);
2261
2255
                        fd_data[ready_fd].buf = buf;
2262
2256
                        fd_data[ready_fd].sz = h;
2312
2306
    close((int)fd);
2313
2307
}
2314
2308
 
2315
 
/*
2316
 
** Async opertation support
2317
 
*/
2318
 
#if defined(USE_THREADS) && !defined(ERTS_SMP)
2319
 
static void
2320
 
sys_async_ready_failed(int fd, int r, int err)
2321
 
{
2322
 
    char buf[120];
2323
 
    sprintf(buf, "sys_async_ready(): Fatal error: fd=%d, r=%d, errno=%d\n",
2324
 
             fd, r, err);
2325
 
    erts_silence_warn_unused_result(write(2, buf, strlen(buf)));
2326
 
    abort();
2327
 
}
2328
 
 
2329
 
/* called from threads !! */
2330
 
void sys_async_ready(int fd)
2331
 
{
2332
 
    int r;
2333
 
    while (1) {
2334
 
        r = write(fd, "0", 1);  /* signal main thread fd MUST be async_fd[1] */
2335
 
        if (r == 1) {
2336
 
            DEBUGF(("sys_async_ready(): r = 1\r\n"));
2337
 
            break;
2338
 
        }
2339
 
        if (r < 0 && errno == EINTR) {
2340
 
            DEBUGF(("sys_async_ready(): r = %d\r\n", r));
2341
 
            continue;
2342
 
        }
2343
 
        sys_async_ready_failed(fd, r, errno);
2344
 
    }
2345
 
}
2346
 
 
2347
 
static int async_drv_init(void)
2348
 
{
2349
 
    async_fd[0] = -1;
2350
 
    async_fd[1] = -1;
2351
 
    return 0;
2352
 
}
2353
 
 
2354
 
static ErlDrvData async_drv_start(ErlDrvPort port_num,
2355
 
                                  char* name, SysDriverOpts* opts)
2356
 
{
2357
 
    if (async_fd[0] != -1)
2358
 
        return ERL_DRV_ERROR_GENERAL;
2359
 
    if (pipe(async_fd) < 0)
2360
 
        return ERL_DRV_ERROR_GENERAL;
2361
 
 
2362
 
    DEBUGF(("async_drv_start: %d\r\n", port_num));
2363
 
 
2364
 
    SET_NONBLOCKING(async_fd[0]);
2365
 
    driver_select(port_num, async_fd[0], ERL_DRV_READ, 1);
2366
 
 
2367
 
    if (init_async(async_fd[1]) < 0)
2368
 
        return ERL_DRV_ERROR_GENERAL;
2369
 
    return (ErlDrvData)port_num;
2370
 
}
2371
 
 
2372
 
static void async_drv_stop(ErlDrvData e)
2373
 
{
2374
 
    int port_num = (int)(long)e;
2375
 
 
2376
 
    DEBUGF(("async_drv_stop: %d\r\n", port_num));
2377
 
 
2378
 
    exit_async();
2379
 
 
2380
 
    driver_select(port_num, async_fd[0], ERL_DRV_READ, 0);
2381
 
 
2382
 
    close(async_fd[0]);
2383
 
    close(async_fd[1]);
2384
 
    async_fd[0] = async_fd[1] = -1;
2385
 
}
2386
 
 
2387
 
 
2388
 
static void async_drv_input(ErlDrvData e, ErlDrvEvent fd)
2389
 
{
2390
 
    char *buf[32];
2391
 
    DEBUGF(("async_drv_input\r\n"));
2392
 
    while (read((int) fd, (void *) buf, 32) > 0); /* fd MUST be async_fd[0] */
2393
 
    check_async_ready();  /* invoke all async_ready */
2394
 
}
2395
 
#endif
2396
2309
 
2397
2310
void erts_do_break_handling(void)
2398
2311
{
2404
2317
     * therefore, make sure that all threads but this one are blocked before
2405
2318
     * proceeding!
2406
2319
     */
2407
 
    erts_smp_block_system(0);
2408
 
    /*
2409
 
     * NOTE: since we allow gc we are not allowed to lock
2410
 
     *       (any) process main locks while blocking system...
2411
 
     */
 
2320
    erts_smp_thr_progress_block();
2412
2321
 
2413
2322
    /* during break we revert to initial settings */
2414
2323
    /* this is done differently for oldshell */
2436
2345
      tcsetattr(0,TCSANOW,&temp_mode);
2437
2346
    }
2438
2347
 
2439
 
    erts_smp_release_system();
 
2348
    erts_smp_thr_progress_unblock();
2440
2349
}
2441
2350
 
2442
2351
/* Fills in the systems representation of the jam/beam process identifier.
2460
2369
#else
2461
2370
    Uint sz = strlen(buffer)+1;
2462
2371
    env = erts_alloc(ERTS_ALC_T_PUTENV_STR, sz);
2463
 
    erts_smp_atomic_add(&sys_misc_mem_sz, sz);
 
2372
    erts_smp_atomic_add_nob(&sys_misc_mem_sz, sz);
2464
2373
    strcpy(env,buffer);
2465
2374
#endif
2466
2375
    erts_smp_rwmtx_rwlock(&environ_rwmtx);
2470
2379
}
2471
2380
 
2472
2381
int
2473
 
erts_sys_getenv(char *key, char *value, size_t *size)
 
2382
erts_sys_getenv__(char *key, char *value, size_t *size)
2474
2383
{
2475
 
    char *orig_value;
2476
2384
    int res;
2477
 
    erts_smp_rwmtx_rlock(&environ_rwmtx);
2478
 
    orig_value = getenv(key);
 
2385
    char *orig_value = getenv(key);
2479
2386
    if (!orig_value)
2480
2387
        res = -1;
2481
2388
    else {
2490
2397
            res = 0;
2491
2398
        }
2492
2399
    }
 
2400
    return res;
 
2401
}
 
2402
 
 
2403
int
 
2404
erts_sys_getenv(char *key, char *value, size_t *size)
 
2405
{
 
2406
    int res;
 
2407
    erts_smp_rwmtx_rlock(&environ_rwmtx);
 
2408
    res = erts_sys_getenv__(key, value, size);
2493
2409
    erts_smp_rwmtx_runlock(&environ_rwmtx);
2494
2410
    return res;
2495
2411
}
2499
2415
{
2500
2416
    fd_data = (struct fd_data *)
2501
2417
        erts_alloc(ERTS_ALC_T_FD_TAB, max_files * sizeof(struct fd_data));
2502
 
    erts_smp_atomic_add(&sys_misc_mem_sz,
2503
 
                        max_files * sizeof(struct fd_data));
2504
 
 
2505
 
#ifdef USE_THREADS
2506
 
#ifdef ERTS_SMP
2507
 
    if (init_async(-1) < 0)
2508
 
        erl_exit(1, "Failed to initialize async-threads\n");
2509
 
#else
2510
 
    {
2511
 
        /* This is speical stuff, starting a driver from the 
2512
 
         * system routines, but is a nice way of handling stuff
2513
 
         * the erlang way
2514
 
         */
2515
 
        SysDriverOpts dopts;
2516
 
        int ret;
2517
 
 
2518
 
        sys_memset((void*)&dopts, 0, sizeof(SysDriverOpts));
2519
 
        add_driver_entry(&async_driver_entry);
2520
 
        ret = erts_open_driver(NULL, NIL, "async", &dopts, NULL);
2521
 
        DEBUGF(("open_driver = %d\n", ret));
2522
 
        if (ret < 0)
2523
 
            erl_exit(1, "Failed to open async driver\n");
2524
 
        erts_port[ret].status |= ERTS_PORT_SFLG_IMMORTAL;
2525
 
    }
2526
 
#endif
2527
 
#endif
2528
 
 
 
2418
    erts_smp_atomic_add_nob(&sys_misc_mem_sz,
 
2419
                            max_files * sizeof(struct fd_data));
2529
2420
}
2530
2421
 
2531
2422
#if (0) /* unused? */
2752
2643
    rep->next = report_exit_transit_list;
2753
2644
    rep->status = status;
2754
2645
    report_exit_transit_list = rep;
2755
 
    /*
2756
 
     * We need the scheduler thread to call check_children().
2757
 
     * If the scheduler thread is sleeping in a poll with a
2758
 
     * timeout, we need to wake the scheduler thread. We use the
2759
 
     * functionality of the async driver to do this, instead of
2760
 
     * implementing yet another driver doing the same thing. A
2761
 
     * little bit ugly, but it works...
2762
 
     */
2763
 
    sys_async_ready(async_fd[1]);
 
2646
    erts_sys_schedule_interrupt(1);
2764
2647
}
2765
2648
 
2766
2649
static int check_children(void)
2847
2730
{
2848
2731
#ifdef ERTS_SMP
2849
2732
    ERTS_CHK_IO(!runnable);
2850
 
    ERTS_SMP_LC_ASSERT(!ERTS_LC_IS_BLOCKING);
2851
2733
#else
2852
 
    ERTS_CHK_IO_INTR(0);
2853
 
    if (runnable) {
2854
 
        ERTS_CHK_IO(0);         /* Poll for I/O */
2855
 
        check_async_ready();    /* Check async completions */
2856
 
    } else {
2857
 
        int wait_for_io = !check_async_ready();
2858
 
        if (wait_for_io)
2859
 
            wait_for_io = !check_children();
2860
 
        ERTS_CHK_IO(wait_for_io);
2861
 
    }
 
2734
    ERTS_CHK_IO(runnable ? 0 : !check_children());
 
2735
#endif
 
2736
    ERTS_SMP_LC_ASSERT(!erts_thr_progress_is_blocking());
2862
2737
    (void) check_children();
2863
 
#endif
2864
2738
}
2865
2739
 
2866
2740
 
2888
2762
static void *
2889
2763
signal_dispatcher_thread_func(void *unused)
2890
2764
{
 
2765
#if !CHLDWTHR
2891
2766
    int initialized = 0;
2892
 
#if !CHLDWTHR
2893
2767
    int notify_check_children = 0;
2894
2768
#endif
2895
2769
#ifdef ERTS_ENABLE_LOCK_CHECK
2917
2791
             *         to other threads.
2918
2792
             *
2919
2793
             * NOTE 2: The signal dispatcher thread is not a blockable
2920
 
             *         thread (i.e., it hasn't called 
2921
 
             *         erts_register_blockable_thread()). This is
2922
 
             *         intentional. We want to be able to interrupt
2923
 
             *         writing of a crash dump by hitting C-c twice.
2924
 
             *         Since it isn't a blockable thread it is important
2925
 
             *         that it doesn't change the state of any data that
2926
 
             *         a blocking thread expects to have exclusive access
2927
 
             *         to (unless the signal dispatcher itself explicitly
2928
 
             *         is blocking all blockable threads).
 
2794
             *         thread (i.e., not a thread managed by the
 
2795
             *         erl_thr_progress module). This is intentional.
 
2796
             *         We want to be able to interrupt writing of a crash
 
2797
             *         dump by hitting C-c twice. Since it isn't a
 
2798
             *         blockable thread it is important that it doesn't
 
2799
             *         change the state of any data that a blocking thread
 
2800
             *         expects to have exclusive access to (unless the
 
2801
             *         signal dispatcher itself explicitly is blocking all
 
2802
             *         blockable threads).
2929
2803
             */
2930
2804
            switch (buf[i]) {
2931
2805
            case 0: /* Emulator initialized */
 
2806
#if !CHLDWTHR
2932
2807
                initialized = 1;
2933
 
#if !CHLDWTHR
2934
2808
                if (!notify_check_children)
2935
2809
#endif
2936
2810
                    break;
2965
2839
                         buf[i]);
2966
2840
            }
2967
2841
        }
2968
 
        ERTS_SMP_LC_ASSERT(!ERTS_LC_IS_BLOCKING);
 
2842
        ERTS_SMP_LC_ASSERT(!erts_thr_progress_is_blocking());
2969
2843
    }
2970
2844
    return NULL;
2971
2845
}
2989
2863
                        NULL,
2990
2864
                        &thr_opts);
2991
2865
}
2992
 
 
 
2866
#ifdef __DARWIN__
 
2867
 
 
2868
int erts_darwin_main_thread_pipe[2];
 
2869
int erts_darwin_main_thread_result_pipe[2];
 
2870
 
 
2871
static void initialize_darwin_main_thread_pipes(void) 
 
2872
{
 
2873
    if (pipe(erts_darwin_main_thread_pipe) < 0 || 
 
2874
        pipe(erts_darwin_main_thread_result_pipe) < 0) {
 
2875
        erl_exit(1,"Fatal error initializing Darwin main thread stealing");
 
2876
    }
 
2877
}
 
2878
 
 
2879
#endif
2993
2880
void
2994
2881
erts_sys_main_thread(void)
2995
2882
{
2996
2883
    erts_thread_disable_fpe();
 
2884
#ifdef __DARWIN__
 
2885
    initialize_darwin_main_thread_pipes();
 
2886
#endif
2997
2887
    /* Become signal receiver thread... */
2998
2888
#ifdef ERTS_ENABLE_LOCK_CHECK
2999
2889
    erts_lc_set_thread_name("signal_receiver");
3002
2892
    smp_sig_notify(0); /* Notify initialized */
3003
2893
    while (1) {
3004
2894
        /* Wait for a signal to arrive... */
 
2895
#ifdef __DARWIN__
 
2896
        /*
 
2897
         * The wx driver needs to be able to steal the main thread for Cocoa to
 
2898
         * work properly.
 
2899
         */
 
2900
        fd_set readfds;
 
2901
        int res;
 
2902
 
 
2903
        FD_ZERO(&readfds);
 
2904
        FD_SET(erts_darwin_main_thread_pipe[0], &readfds);
 
2905
        res = select(erts_darwin_main_thread_pipe[0] + 1, &readfds, NULL, NULL, NULL);
 
2906
        if (res > 0 && FD_ISSET(erts_darwin_main_thread_pipe[0],&readfds)) {
 
2907
            void* (*func)(void*);
 
2908
            void* arg;
 
2909
            void *resp;
 
2910
            read(erts_darwin_main_thread_pipe[0],&func,sizeof(void* (*)(void*)));
 
2911
            read(erts_darwin_main_thread_pipe[0],&arg, sizeof(void*));
 
2912
            resp = (*func)(arg);
 
2913
            write(erts_darwin_main_thread_result_pipe[1],&resp,sizeof(void *));
 
2914
        }
 
2915
#else
3005
2916
#ifdef DEBUG
3006
2917
        int res =
3007
2918
#else
3010
2921
            select(0, NULL, NULL, NULL, NULL);
3011
2922
        ASSERT(res < 0);
3012
2923
        ASSERT(errno == EINTR);
 
2924
#endif
3013
2925
    }
3014
2926
}
3015
2927
 
3047
2959
{
3048
2960
    int i, j;
3049
2961
 
 
2962
    erts_smp_rwmtx_init(&environ_rwmtx, "environ");
 
2963
 
3050
2964
    i = 1;
3051
2965
 
3052
2966
    ASSERT(argc && argv);
3108
3022
            argv[j++] = argv[i];
3109
3023
    }
3110
3024
    *argc = j;
3111
 
}
3112
 
 
3113
 
#ifdef ERTS_TIMER_THREAD
3114
 
 
3115
 
/*
3116
 
 * Interruptible-wait facility: low-level synchronisation state
3117
 
 * and methods that are implementation dependent.
3118
 
 *
3119
 
 * Constraint: Every implementation must define 'struct erts_iwait'
3120
 
 * with a field 'erts_smp_atomic_t state;'.
3121
 
 */
3122
 
 
3123
 
/* values for struct erts_iwait's state field */
3124
 
#define IWAIT_WAITING   0
3125
 
#define IWAIT_AWAKE     1
3126
 
#define IWAIT_INTERRUPT 2
3127
 
 
3128
 
#if 0   /* XXX: needs feature test in erts/configure.in */
3129
 
 
3130
 
/*
3131
 
 * This is an implementation of the interruptible wait facility on
3132
 
 * top of Linux-specific futexes.
3133
 
 */
3134
 
#include <asm/unistd.h>
3135
 
#define FUTEX_WAIT              0
3136
 
#define FUTEX_WAKE              1
3137
 
static int sys_futex(void *futex, int op, int val, const struct timespec *timeout)
3138
 
{
3139
 
    return syscall(__NR_futex, futex, op, val, timeout);
3140
 
}
3141
 
 
3142
 
struct erts_iwait {
3143
 
    erts_smp_atomic_t state; /* &state.counter is our futex */
3144
 
};
3145
 
 
3146
 
static void iwait_lowlevel_init(struct erts_iwait *iwait) { /* empty */ }
3147
 
 
3148
 
static void iwait_lowlevel_wait(struct erts_iwait *iwait, struct timeval *delay)
3149
 
{
3150
 
    struct timespec timeout;
3151
 
    int res;
3152
 
 
3153
 
    timeout.tv_sec = delay->tv_sec;
3154
 
    timeout.tv_nsec = delay->tv_usec * 1000;
3155
 
    res = sys_futex((void*)&iwait->state.counter, FUTEX_WAIT, IWAIT_WAITING, &timeout);
3156
 
    if (res < 0 && errno != ETIMEDOUT && errno != EWOULDBLOCK && errno != EINTR)
3157
 
        perror("FUTEX_WAIT");
3158
 
}
3159
 
 
3160
 
static void iwait_lowlevel_interrupt(struct erts_iwait *iwait)
3161
 
{
3162
 
    int res = sys_futex((void*)&iwait->state.counter, FUTEX_WAKE, 1, NULL);
3163
 
    if (res < 0)
3164
 
        perror("FUTEX_WAKE");
3165
 
}
3166
 
 
3167
 
#else   /* using poll() or select() */
3168
 
 
3169
 
/*
3170
 
 * This is an implementation of the interruptible wait facility on
3171
 
 * top of pipe(), poll() or select(), read(), and write().
3172
 
 */
3173
 
struct erts_iwait {
3174
 
    erts_smp_atomic_t state;
3175
 
    int read_fd;        /* wait polls and reads this fd */
3176
 
    int write_fd;       /* interrupt writes this fd */
3177
 
};
3178
 
 
3179
 
static void iwait_lowlevel_init(struct erts_iwait *iwait)
3180
 
{
3181
 
    int fds[2];
3182
 
 
3183
 
    if (pipe(fds) < 0) {
3184
 
        perror("pipe()");
3185
 
        exit(1);
3186
 
    }
3187
 
    iwait->read_fd = fds[0];
3188
 
    iwait->write_fd = fds[1];
3189
 
}
3190
 
 
3191
 
#if defined(ERTS_USE_POLL)
3192
 
 
3193
 
#include <sys/poll.h>
3194
 
#define PERROR_POLL "poll()"
3195
 
 
3196
 
static int iwait_lowlevel_poll(int read_fd, struct timeval *delay)
3197
 
{
3198
 
    struct pollfd pollfd;
3199
 
    int timeout;
3200
 
 
3201
 
    pollfd.fd = read_fd;
3202
 
    pollfd.events = POLLIN;
3203
 
    pollfd.revents = 0;
3204
 
    timeout = delay->tv_sec * 1000 + delay->tv_usec / 1000;
3205
 
    return poll(&pollfd, 1, timeout);
3206
 
}
3207
 
 
3208
 
#else   /* !ERTS_USE_POLL */
3209
 
 
3210
 
#include <sys/select.h>
3211
 
#define PERROR_POLL "select()"
3212
 
 
3213
 
static int iwait_lowlevel_poll(int read_fd, struct timeval *delay)
3214
 
{
3215
 
    fd_set readfds;
3216
 
 
3217
 
    FD_ZERO(&readfds);
3218
 
    FD_SET(read_fd, &readfds);
3219
 
    return select(read_fd + 1, &readfds, NULL, NULL, delay);
3220
 
}
3221
 
 
3222
 
#endif  /* !ERTS_USE_POLL */
3223
 
 
3224
 
static void iwait_lowlevel_wait(struct erts_iwait *iwait, struct timeval *delay)
3225
 
{
3226
 
    int res;
3227
 
    char buf[64];
3228
 
 
3229
 
    res = iwait_lowlevel_poll(iwait->read_fd, delay);
3230
 
    if (res > 0)
3231
 
        (void)read(iwait->read_fd, buf, sizeof buf);
3232
 
    else if (res < 0 && errno != EINTR)
3233
 
        perror(PERROR_POLL);
3234
 
}
3235
 
 
3236
 
static void iwait_lowlevel_interrupt(struct erts_iwait *iwait)
3237
 
{
3238
 
    int res = write(iwait->write_fd, "!", 1);
3239
 
    if (res < 0)
3240
 
        perror("write()");
3241
 
}
3242
 
 
3243
 
#endif  /* using poll() or select() */
3244
 
 
3245
 
#if 0   /* not using poll() or select() */
3246
 
/*
3247
 
 * This is an implementation of the interruptible wait facility on
3248
 
 * top of pthread_cond_timedwait(). This has two problems:
3249
 
 * 1. pthread_cond_timedwait() requires an absolute time point,
3250
 
 *    so the relative delay must be converted to absolute time.
3251
 
 *    Worse, this breaks if the machine's time is adjusted while
3252
 
 *    we're preparing to wait.
3253
 
 * 2. Each cond operation requires additional mutex lock/unlock operations.
3254
 
 *
3255
 
 * Problem 2 is probably not too bad on Linux (they'll just become
3256
 
 * relatively cheap futex operations), but problem 1 is the real killer.
3257
 
 * Only use this implementation if no better alternatives are available!
3258
 
 */
3259
 
struct erts_iwait {
3260
 
    erts_smp_atomic_t state;
3261
 
    pthread_cond_t cond;
3262
 
    pthread_mutex_t mutex;
3263
 
};
3264
 
 
3265
 
static void iwait_lowlevel_init(struct erts_iwait *iwait)
3266
 
{
3267
 
    iwait->cond = (pthread_cond_t) PTHREAD_COND_INITIALIZER;
3268
 
    iwait->mutex = (pthread_mutex_t) PTHREAD_MUTEX_INITIALIZER;
3269
 
}
3270
 
 
3271
 
static void iwait_lowlevel_wait(struct erts_iwait *iwait, struct timeval *delay)
3272
 
{
3273
 
    struct timeval tmp;
3274
 
    struct timespec timeout;
3275
 
 
3276
 
    /* Due to pthread_cond_timedwait()'s use of absolute
3277
 
       time, this must be the real gettimeofday(), _not_
3278
 
       the "smoothed" one beam/erl_time_sup.c implements. */
3279
 
    gettimeofday(&tmp, NULL);
3280
 
 
3281
 
    tmp.tv_sec += delay->tv_sec;
3282
 
    tmp.tv_usec += delay->tv_usec;
3283
 
    if (tmp.tv_usec >= 1000*1000) {
3284
 
        tmp.tv_usec -= 1000*1000;
3285
 
        tmp.tv_sec += 1;
3286
 
    }
3287
 
    timeout.tv_sec = tmp.tv_sec;
3288
 
    timeout.tv_nsec = tmp.tv_usec * 1000;
3289
 
    pthread_mutex_lock(&iwait->mutex);
3290
 
    pthread_cond_timedwait(&iwait->cond, &iwait->mutex, &timeout);
3291
 
    pthread_mutex_unlock(&iwait->mutex);
3292
 
}
3293
 
 
3294
 
static void iwait_lowlevel_interrupt(struct erts_iwait *iwait)
3295
 
{
3296
 
    pthread_mutex_lock(&iwait->mutex);
3297
 
    pthread_cond_signal(&iwait->cond);
3298
 
    pthread_mutex_unlock(&iwait->mutex);
3299
 
}
3300
 
 
3301
 
#endif /* not using POLL */
3302
 
 
3303
 
/*
3304
 
 * Interruptible-wait facility. This is just a wrapper around the
3305
 
 * low-level synchronisation code, where we maintain our logical
3306
 
 * state in order to suppress some state transitions.
3307
 
 */
3308
 
 
3309
 
struct erts_iwait *erts_iwait_init(void)
3310
 
{
3311
 
    struct erts_iwait *iwait = malloc(sizeof *iwait);
3312
 
    if (!iwait) {
3313
 
        perror("malloc");
3314
 
        exit(1);
3315
 
    }
3316
 
    iwait_lowlevel_init(iwait);
3317
 
    erts_smp_atomic_init(&iwait->state, IWAIT_AWAKE);
3318
 
    return iwait;
3319
 
}
3320
 
 
3321
 
void erts_iwait_wait(struct erts_iwait *iwait, struct timeval *delay)
3322
 
{
3323
 
    if (erts_smp_atomic_xchg(&iwait->state, IWAIT_WAITING) != IWAIT_INTERRUPT)
3324
 
        iwait_lowlevel_wait(iwait, delay);
3325
 
    erts_smp_atomic_set(&iwait->state, IWAIT_AWAKE);
3326
 
}
3327
 
 
3328
 
void erts_iwait_interrupt(struct erts_iwait *iwait)
3329
 
{
3330
 
    if (erts_smp_atomic_xchg(&iwait->state, IWAIT_INTERRUPT) == IWAIT_WAITING)
3331
 
        iwait_lowlevel_interrupt(iwait);
3332
 
}
3333
 
 
3334
 
#endif /* ERTS_TIMER_THREAD */
 
3025
 
 
3026
}