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

« back to all changes in this revision

Viewing changes to erts/emulator/beam/bif.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
36
36
#include "beam_bp.h"
37
37
#include "erl_db_util.h"
38
38
#include "register.h"
 
39
#include "erl_thr_progress.h"
39
40
 
40
41
static Export* flush_monitor_message_trap = NULL;
41
42
static Export* set_cpu_topology_trap = NULL;
368
369
   ErtsMonitor *mon = NULL;  /* The monitor entry to delete */
369
370
   Process  *rp;    /* Local target process */
370
371
   Eterm     to = NIL;    /* Monitor link traget */
371
 
   Eterm     ref_p; /* Pid of this end */
372
372
   DistEntry *dep = NULL;  /* Target's distribution entry */
373
373
   int deref_de = 0;
374
374
   int res;
381
381
       res = ERTS_DEMONITOR_BADARG;
382
382
       goto done; /* Cannot be this monitor's ref */
383
383
   }
384
 
   ref_p = c_p->id;
385
384
 
386
385
   mon = erts_lookup_monitor(c_p->monitors, ref);
387
386
   if (!mon) {
813
812
    so.min_heap_size  = H_MIN_SIZE;
814
813
    so.min_vheap_size = BIN_VH_MIN_SIZE;
815
814
    so.priority       = PRIORITY_NORMAL;
816
 
    so.max_gen_gcs    = (Uint16) erts_smp_atomic_read(&erts_max_gen_gcs);
 
815
    so.max_gen_gcs    = (Uint16) erts_smp_atomic32_read_nob(&erts_max_gen_gcs);
817
816
    so.scheduler      = 0;
818
817
 
819
818
    /*
871
870
                }
872
871
            } else if (arg == am_scheduler && is_small(val)) {
873
872
                Sint scheduler = signed_val(val);
874
 
                if (erts_common_run_queue && erts_no_schedulers > 1)
875
 
                    goto error;
876
873
                if (scheduler < 0 || erts_no_schedulers < scheduler)
877
874
                    goto error;
878
875
                so.scheduler = (int) scheduler;
1091
1088
BIF_RETTYPE hibernate_3(BIF_ALIST_3)
1092
1089
{
1093
1090
    /*
1094
 
     * hibernate/3 is implemented as an instruction; therefore
1095
 
     * this function will never be called.
 
1091
     * hibernate/3 is usually translated to an instruction; therefore
 
1092
     * this function is only called from HiPE or when the call could not
 
1093
     * be translated.
1096
1094
     */
1097
 
    BIF_ERROR(BIF_P, BADARG);
 
1095
    Eterm reg[3];
 
1096
 
 
1097
    if (erts_hibernate(BIF_P, BIF_ARG_1, BIF_ARG_2, BIF_ARG_3, reg)) {
 
1098
        /*
 
1099
         * If hibernate succeeded, TRAP. The process will be suspended
 
1100
         * if status is P_WAITING or continue (if any message was in the queue).
 
1101
         */
 
1102
        BIF_TRAP_CODE_PTR_(BIF_P, BIF_P->i);
 
1103
    }
 
1104
    return THE_NON_VALUE;
1098
1105
}
1099
1106
 
1100
1107
/**********************************************************************/
1101
1108
 
1102
 
BIF_RETTYPE get_stacktrace_0(Process* p)
 
1109
BIF_RETTYPE get_stacktrace_0(BIF_ALIST_0)
1103
1110
{
1104
 
    Eterm t = build_stacktrace(p, p->ftrace);
 
1111
    Eterm t = build_stacktrace(BIF_P, BIF_P->ftrace);
1105
1112
    BIF_RET(t);
1106
1113
}
1107
1114
 
1111
1118
 * the process, and the final error value will be {Term,StackTrace}.
1112
1119
 */
1113
1120
 
1114
 
BIF_RETTYPE error_1(Process* p, Eterm term)
 
1121
BIF_RETTYPE error_1(BIF_ALIST_1)
1115
1122
{
1116
 
    p->fvalue = term;
1117
 
    BIF_ERROR(p, EXC_ERROR);
 
1123
    BIF_P->fvalue = BIF_ARG_1;
 
1124
    BIF_ERROR(BIF_P, EXC_ERROR);
1118
1125
}
1119
1126
 
1120
1127
/**********************************************************************/
1123
1130
 * in the stacktrace.
1124
1131
 */
1125
1132
 
1126
 
BIF_RETTYPE error_2(Process* p, Eterm value, Eterm args)
 
1133
BIF_RETTYPE error_2(BIF_ALIST_2)
1127
1134
{
1128
 
    Eterm* hp = HAlloc(p, 3);
 
1135
    Eterm* hp = HAlloc(BIF_P, 3);
1129
1136
 
1130
 
    p->fvalue = TUPLE2(hp, value, args);
1131
 
    BIF_ERROR(p, EXC_ERROR_2);
 
1137
    BIF_P->fvalue = TUPLE2(hp, BIF_ARG_1, BIF_ARG_2);
 
1138
    BIF_ERROR(BIF_P, EXC_ERROR_2);
1132
1139
}
1133
1140
 
1134
1141
/**********************************************************************/
1138
1145
 * It is useful in stub functions for NIFs.
1139
1146
 */
1140
1147
 
1141
 
BIF_RETTYPE nif_error_1(Process* p, Eterm term)
 
1148
BIF_RETTYPE nif_error_1(BIF_ALIST_1)
1142
1149
{
1143
 
    p->fvalue = term;
1144
 
    BIF_ERROR(p, EXC_ERROR);
 
1150
    BIF_P->fvalue = BIF_ARG_1;
 
1151
    BIF_ERROR(BIF_P, EXC_ERROR);
1145
1152
}
1146
1153
 
1147
1154
/**********************************************************************/
1151
1158
 * It is useful in stub functions for NIFs.
1152
1159
 */
1153
1160
 
1154
 
BIF_RETTYPE nif_error_2(Process* p, Eterm value, Eterm args)
 
1161
BIF_RETTYPE nif_error_2(BIF_ALIST_2)
1155
1162
{
1156
 
    Eterm* hp = HAlloc(p, 3);
 
1163
    Eterm* hp = HAlloc(BIF_P, 3);
1157
1164
 
1158
 
    p->fvalue = TUPLE2(hp, value, args);
1159
 
    BIF_ERROR(p, EXC_ERROR_2);
 
1165
    BIF_P->fvalue = TUPLE2(hp, BIF_ARG_1, BIF_ARG_2);
 
1166
    BIF_ERROR(BIF_P, EXC_ERROR_2);
1160
1167
}
1161
1168
 
1162
1169
/**********************************************************************/
1175
1182
 * If there is an error in the argument format, 
1176
1183
 * return the atom 'badarg' instead.
1177
1184
 */
1178
 
Eterm 
1179
 
raise_3(Process *c_p, Eterm class, Eterm value, Eterm stacktrace) {
 
1185
BIF_RETTYPE raise_3(BIF_ALIST_3)
 
1186
{
 
1187
    Process *c_p = BIF_P;
 
1188
    Eterm class = BIF_ARG_1;
 
1189
    Eterm value = BIF_ARG_2;
 
1190
    Eterm stacktrace = BIF_ARG_3;
1180
1191
    Eterm reason;
1181
1192
    Eterm l, *hp, *hp_end, *tp;
1182
1193
    int depth, cnt;
1183
1194
    size_t sz;
 
1195
    int must_copy = 0;
1184
1196
    struct StackTrace *s;
1185
 
    
 
1197
 
1186
1198
    if (class == am_error) {
1187
1199
        c_p->fvalue = value;
1188
1200
        reason = EXC_ERROR;
1198
1210
    /* Check syntax of stacktrace, and count depth.
1199
1211
     * Accept anything that can be returned from erlang:get_stacktrace/0,
1200
1212
     * as well as a 2-tuple with a fun as first element that the
1201
 
     * error_handler may need to give us.
 
1213
     * error_handler may need to give us. Also allow old-style
 
1214
     * MFA three-tuples.
1202
1215
     */
1203
1216
    for (l = stacktrace, depth = 0;  
1204
1217
         is_list(l);  
1205
1218
         l = CDR(list_val(l)), depth++) {
1206
1219
        Eterm t = CAR(list_val(l));
1207
 
        int arity;
 
1220
        Eterm location = NIL;
 
1221
 
1208
1222
        if (is_not_tuple(t)) goto error;
1209
1223
        tp = tuple_val(t);
1210
 
        arity = arityval(tp[0]);
1211
 
        if ((arity == 3) && is_atom(tp[1]) && is_atom(tp[2])) continue;
1212
 
        if ((arity == 2) && is_fun(tp[1])) continue;
1213
 
        goto error;
 
1224
        switch (arityval(tp[0])) {
 
1225
        case 2:
 
1226
            /* {Fun,Args} */
 
1227
            if (is_fun(tp[1])) {
 
1228
                must_copy = 1;
 
1229
            } else {
 
1230
                goto error;
 
1231
            }
 
1232
            break;
 
1233
        case 3:
 
1234
            /*
 
1235
             * One of:
 
1236
             * {Fun,Args,Location}
 
1237
             * {M,F,A}
 
1238
             */
 
1239
            if (is_fun(tp[1])) {
 
1240
                location = tp[3];
 
1241
            } else if (is_atom(tp[1]) && is_atom(tp[2])) {
 
1242
                must_copy = 1;
 
1243
            } else {
 
1244
                goto error;
 
1245
            }
 
1246
            break;
 
1247
        case 4:
 
1248
            if (!(is_atom(tp[1]) && is_atom(tp[2]))) {
 
1249
                goto error;
 
1250
            }
 
1251
            location = tp[4];
 
1252
            break;
 
1253
        default:
 
1254
            goto error;
 
1255
        }
 
1256
        if (is_not_list(location) && is_not_nil(location)) {
 
1257
            goto error;
 
1258
        }
1214
1259
    }
1215
1260
    if (is_not_nil(l)) goto error;
1216
1261
    
1217
1262
    /* Create stacktrace and store */
1218
 
    if (depth <= erts_backtrace_depth) {
 
1263
    if (erts_backtrace_depth < depth) {
 
1264
        depth = erts_backtrace_depth;
 
1265
        must_copy = 1;
 
1266
    }
 
1267
    if (must_copy) {
 
1268
        cnt = depth;
 
1269
        c_p->ftrace = NIL;
 
1270
    } else {
 
1271
        /* No need to copy the stacktrace */
1219
1272
        cnt = 0;
1220
1273
        c_p->ftrace = stacktrace;
1221
 
    } else {
1222
 
        cnt = depth = erts_backtrace_depth;
1223
 
        c_p->ftrace = NIL;
1224
1274
    }
 
1275
 
1225
1276
    tp = &c_p->ftrace;
1226
1277
    sz = (offsetof(struct StackTrace, trace) + sizeof(Eterm) - 1) 
1227
1278
        / sizeof(Eterm);
1228
 
    hp = HAlloc(c_p, sz + 2*(cnt + 1));
1229
 
    hp_end = hp + sz + 2*(cnt + 1);
 
1279
    hp = HAlloc(c_p, sz + (2+6)*(cnt + 1));
 
1280
    hp_end = hp + sz + (2+6)*(cnt + 1);
1230
1281
    s = (struct StackTrace *) hp;
1231
1282
    s->header = make_neg_bignum_header(sz - 1);
1232
1283
    s->freason = reason;
1234
1285
    s->current = NULL;
1235
1286
    s->depth = 0;
1236
1287
    hp += sz;
1237
 
    if (cnt > 0) {
 
1288
    if (must_copy) {
 
1289
        int cnt;
 
1290
 
1238
1291
        /* Copy list up to depth */
1239
1292
        for (cnt = 0, l = stacktrace;
1240
1293
             cnt < depth;
1241
1294
             cnt++, l = CDR(list_val(l))) {
 
1295
            Eterm t;
 
1296
            Eterm *tpp;
 
1297
            int arity;
 
1298
 
1242
1299
            ASSERT(*tp == NIL);
1243
 
            *tp = CONS(hp, CAR(list_val(l)), *tp);
 
1300
            t = CAR(list_val(l));
 
1301
            tpp = tuple_val(t);
 
1302
            arity = arityval(tpp[0]);
 
1303
            if (arity == 2) {
 
1304
                t = TUPLE3(hp, tpp[1], tpp[2], NIL);
 
1305
                hp += 4;
 
1306
            } else if (arity == 3 && is_atom(tpp[1])) {
 
1307
                t = TUPLE4(hp, tpp[1], tpp[2], tpp[3], NIL);
 
1308
                hp += 5;
 
1309
            }
 
1310
            *tp = CONS(hp, t, *tp);
1244
1311
            tp = &CDR(list_val(*tp));
1245
1312
            hp += 2;
1246
1313
        }
1248
1315
    c_p->ftrace = CONS(hp, c_p->ftrace, make_big((Eterm *) s));
1249
1316
    hp += 2;
1250
1317
    ASSERT(hp <= hp_end);
1251
 
    
 
1318
    HRelease(c_p, hp_end, hp);
1252
1319
    BIF_ERROR(c_p, reason);
1253
1320
    
1254
1321
 error:
1351
1418
#ifdef ERTS_SMP
1352
1419
         if (rp == BIF_P)
1353
1420
             rp_locks &= ~ERTS_PROC_LOCK_MAIN;
1354
 
         else
 
1421
         if (rp_locks)
 
1422
             erts_smp_proc_unlock(rp, rp_locks);
 
1423
         if (rp != BIF_P)
1355
1424
             erts_smp_proc_dec_refc(rp);
1356
 
         erts_smp_proc_unlock(rp, rp_locks);
1357
1425
#endif
1358
1426
         /*
1359
1427
          * We may have exited ourselves and may have to take action.
1465
1533
       ErtsRunQueue *old;
1466
1534
       ErtsRunQueue *new;
1467
1535
       Sint sched;
1468
 
       if (erts_common_run_queue && erts_no_schedulers > 1)
1469
 
           goto error;
1470
1536
       if (!is_small(BIF_ARG_2))
1471
1537
           goto error;
1472
1538
       sched = signed_val(BIF_ARG_2);
1665
1731
 * erlang:'!'/2
1666
1732
 */
1667
1733
 
1668
 
Eterm
1669
 
ebif_bang_2(Process* p, Eterm To, Eterm Message)
 
1734
BIF_RETTYPE
 
1735
ebif_bang_2(BIF_ALIST_2)
1670
1736
{
1671
 
    return send_2(p, To, Message);
 
1737
    return erl_send(BIF_P, BIF_ARG_1, BIF_ARG_2);
1672
1738
}
1673
1739
 
1674
1740
 
2005
2071
}
2006
2072
 
2007
2073
 
2008
 
Eterm
2009
 
send_3(Process *p, Eterm to, Eterm msg, Eterm opts) {
 
2074
BIF_RETTYPE send_3(BIF_ALIST_3)
 
2075
{
 
2076
    Process *p = BIF_P;
 
2077
    Eterm to = BIF_ARG_1;
 
2078
    Eterm msg = BIF_ARG_2;
 
2079
    Eterm opts = BIF_ARG_3;
 
2080
 
2010
2081
    int connect = !0;
2011
2082
    int suspend = !0;
2012
2083
    Eterm l = opts;
2070
2141
    BIF_ERROR(p, BADARG);
2071
2142
}
2072
2143
 
2073
 
Eterm
2074
 
send_2(Process *p, Eterm to, Eterm msg) {
 
2144
BIF_RETTYPE send_2(BIF_ALIST_2)
 
2145
{
 
2146
    return erl_send(BIF_P, BIF_ARG_1, BIF_ARG_2);
 
2147
}
 
2148
 
 
2149
Eterm erl_send(Process *p, Eterm to, Eterm msg)
 
2150
{
2075
2151
    Sint result = do_send(p, to, msg, !0);
2076
2152
    
2077
2153
    if (result > 0) {
2159
2235
/**********************************************************************/
2160
2236
/* return the size of an I/O list */
2161
2237
 
 
2238
static Eterm
 
2239
accumulate(Eterm acc, Uint size)
 
2240
{
 
2241
    if (is_non_value(acc)) {
 
2242
        /*
 
2243
         * There is no pre-existing accumulator. Allocate a
 
2244
         * bignum buffer with one extra word to be used if
 
2245
         * the bignum grows in the future.
 
2246
         */
 
2247
        Eterm* hp = (Eterm *) erts_alloc(ERTS_ALC_T_TEMP_TERM,
 
2248
                                         (BIG_UINT_HEAP_SIZE+1) *
 
2249
                                         sizeof(Eterm));
 
2250
        return uint_to_big(size, hp);
 
2251
    } else {
 
2252
        Eterm* big;
 
2253
        int need_heap;
 
2254
 
 
2255
        /*
 
2256
         * Add 'size' to 'acc' in place. There is always one
 
2257
         * extra word allocated in case the bignum grows by one word.
 
2258
         */
 
2259
        big = big_val(acc);
 
2260
        need_heap = BIG_NEED_SIZE(BIG_SIZE(big));
 
2261
        acc = big_plus_small(acc, size, big);
 
2262
        if (BIG_NEED_SIZE(big_size(acc)) > need_heap) {
 
2263
            /*
 
2264
             * The extra word has been consumed. Grow the
 
2265
             * allocation by one word.
 
2266
             */
 
2267
            big = (Eterm *) erts_realloc(ERTS_ALC_T_TEMP_TERM,
 
2268
                                         big_val(acc),
 
2269
                                         (need_heap+1) * sizeof(Eterm));
 
2270
            acc = make_big(big);
 
2271
        }
 
2272
        return acc;
 
2273
    }
 
2274
}
 
2275
 
 
2276
static Eterm
 
2277
consolidate(Process* p, Eterm acc, Uint size)
 
2278
{
 
2279
    Eterm* hp;
 
2280
 
 
2281
    if (is_non_value(acc)) {
 
2282
        return erts_make_integer(size, p);
 
2283
    } else {
 
2284
        Eterm* big;
 
2285
        Uint sz;
 
2286
        Eterm res;
 
2287
        
 
2288
        acc = accumulate(acc, size);
 
2289
        big = big_val(acc);
 
2290
        sz = BIG_NEED_SIZE(BIG_SIZE(big));
 
2291
        hp = HAlloc(p, sz);
 
2292
        res = make_big(hp);
 
2293
        while (sz--) {
 
2294
            *hp++ = *big++;
 
2295
        }
 
2296
        erts_free(ERTS_ALC_T_TEMP_TERM, (void *) big_val(acc));
 
2297
        return res;
 
2298
    }
 
2299
}
 
2300
 
2162
2301
BIF_RETTYPE iolist_size_1(BIF_ALIST_1)
2163
2302
{
2164
 
    Sint size = io_list_len(BIF_ARG_1);
2165
 
 
2166
 
    if (size == -1) {
2167
 
        BIF_ERROR(BIF_P, BADARG);
2168
 
    } else if (IS_USMALL(0, (Uint) size)) {
2169
 
        BIF_RET(make_small(size));
2170
 
    } else {
2171
 
        Eterm* hp = HAlloc(BIF_P, BIG_UINT_HEAP_SIZE);
2172
 
        BIF_RET(uint_to_big(size, hp));
 
2303
    Eterm obj, hd;
 
2304
    Eterm* objp;
 
2305
    Uint size = 0;
 
2306
    Uint cur_size;
 
2307
    Uint new_size;
 
2308
    Eterm acc = THE_NON_VALUE;
 
2309
    DECLARE_ESTACK(s);
 
2310
 
 
2311
    obj = BIF_ARG_1;
 
2312
    goto L_again;
 
2313
 
 
2314
    while (!ESTACK_ISEMPTY(s)) {
 
2315
        obj = ESTACK_POP(s);
 
2316
    L_again:
 
2317
        if (is_list(obj)) {
 
2318
        L_iter_list:
 
2319
            objp = list_val(obj);
 
2320
            hd = CAR(objp);
 
2321
            obj = CDR(objp);
 
2322
            /* Head */
 
2323
            if (is_byte(hd)) {
 
2324
                size++;
 
2325
                if (size == 0) {
 
2326
                    acc = accumulate(acc, (Uint) -1);
 
2327
                    size = 1;
 
2328
                }
 
2329
            } else if (is_binary(hd) && binary_bitsize(hd) == 0) {
 
2330
                cur_size = binary_size(hd);
 
2331
                if ((new_size = size + cur_size) >= size) {
 
2332
                    size = new_size;
 
2333
                } else {
 
2334
                    acc = accumulate(acc, size);
 
2335
                    size = cur_size;
 
2336
                }
 
2337
            } else if (is_list(hd)) {
 
2338
                ESTACK_PUSH(s, obj);
 
2339
                obj = hd;
 
2340
                goto L_iter_list;
 
2341
            } else if (is_not_nil(hd)) {
 
2342
                goto L_type_error;
 
2343
            }
 
2344
            /* Tail */
 
2345
            if (is_list(obj)) {
 
2346
                goto L_iter_list;
 
2347
            } else if (is_binary(obj) && binary_bitsize(obj) == 0) {
 
2348
                cur_size = binary_size(obj);
 
2349
                if ((new_size = size + cur_size) >= size) {
 
2350
                    size = new_size;
 
2351
                } else {
 
2352
                    acc = accumulate(acc, size);
 
2353
                    size = cur_size;
 
2354
                }
 
2355
            } else if (is_not_nil(obj)) {
 
2356
                goto L_type_error;
 
2357
            }
 
2358
        } else if (is_binary(obj) && binary_bitsize(obj) == 0) {
 
2359
            cur_size = binary_size(obj);
 
2360
            if ((new_size = size + cur_size) >= size) {
 
2361
                size = new_size;
 
2362
            } else {
 
2363
                acc = accumulate(acc, size);
 
2364
                size = cur_size;
 
2365
            }
 
2366
        } else if (is_not_nil(obj)) {
 
2367
            goto L_type_error;
 
2368
        }
2173
2369
    }
 
2370
 
 
2371
    DESTROY_ESTACK(s);
 
2372
    BIF_RET(consolidate(BIF_P, acc, size));
 
2373
 
 
2374
 L_type_error:
 
2375
    DESTROY_ESTACK(s);
 
2376
    BIF_ERROR(BIF_P, BADARG);
2174
2377
}
2175
2378
 
2176
 
 
2177
2379
/**********************************************************************/
2178
2380
 
2179
2381
/* return the N'th element of a tuple */
3121
3323
/* return the universal time */
3122
3324
 
3123
3325
BIF_RETTYPE 
3124
 
localtime_to_universaltime_2(Process *p, Eterm localtime, Eterm dst)
 
3326
localtime_to_universaltime_2(BIF_ALIST_2)
3125
3327
{
 
3328
    Process *p = BIF_P;
 
3329
    Eterm localtime = BIF_ARG_1;
 
3330
    Eterm dst = BIF_ARG_2;
3126
3331
    Sint year, month, day;
3127
3332
    Sint hour, minute, second;
3128
3333
    int isdst;
3180
3385
    BIF_RET(TUPLE2(hp, res1, res2));
3181
3386
}
3182
3387
 
 
3388
/* convert calendar:universaltime_to_seconds/1 */
 
3389
 
 
3390
BIF_RETTYPE universaltime_to_posixtime_1(BIF_ALIST_1)
 
3391
{
 
3392
    Sint year, month, day;
 
3393
    Sint hour, minute, second;
 
3394
 
 
3395
    Sint64 seconds = 0;
 
3396
    Eterm *hp;
 
3397
    Uint hsz = 0;
 
3398
 
 
3399
    if (!time_to_parts(BIF_ARG_1, &year, &month, &day, 
 
3400
                       &hour, &minute, &second))
 
3401
        BIF_ERROR(BIF_P, BADARG);
 
3402
 
 
3403
    if (!univ_to_seconds(year, month, day, hour, minute, second, &seconds)) {
 
3404
        BIF_ERROR(BIF_P, BADARG);
 
3405
    }
 
3406
 
 
3407
    erts_bld_sint64(NULL, &hsz, seconds);
 
3408
    hp = HAlloc(BIF_P, hsz);
 
3409
    BIF_RET(erts_bld_sint64(&hp, NULL, seconds));
 
3410
}
 
3411
 
 
3412
/* convert calendar:seconds_to_universaltime/1 */
 
3413
 
 
3414
BIF_RETTYPE posixtime_to_universaltime_1(BIF_ALIST_1)
 
3415
{
 
3416
    Sint year, month, day;
 
3417
    Sint hour, minute, second;
 
3418
    Eterm res1, res2;
 
3419
    Eterm* hp;
 
3420
 
 
3421
    Sint64 time = 0;
 
3422
 
 
3423
    if (!term_to_Sint64(BIF_ARG_1, &time)) {
 
3424
        BIF_ERROR(BIF_P, BADARG);
 
3425
    }
 
3426
 
 
3427
    if (!seconds_to_univ(time, &year, &month, &day,
 
3428
                &hour, &minute, &second)) {
 
3429
        BIF_ERROR(BIF_P, BADARG);
 
3430
    }
 
3431
 
 
3432
    hp = HAlloc(BIF_P, 4+4+3);
 
3433
    res1 = TUPLE3(hp,make_small(year),make_small(month),
 
3434
                  make_small(day));
 
3435
    hp += 4;
 
3436
    res2 = TUPLE3(hp,make_small(hour),make_small(minute),
 
3437
                  make_small(second));
 
3438
    hp += 4;
 
3439
    BIF_RET(TUPLE2(hp, res1, res2));
 
3440
}
 
3441
 
 
3442
 
3183
3443
/**********************************************************************/
3184
3444
 
3185
3445
 
3206
3466
        BIF_ERROR(BIF_P, BADARG);
3207
3467
    }
3208
3468
 
3209
 
    rp = erts_pid2proc_not_running(BIF_P, ERTS_PROC_LOCK_MAIN,
 
3469
    if (BIF_P->id == BIF_ARG_1)
 
3470
        rp = BIF_P;
 
3471
    else {
 
3472
#ifdef ERTS_SMP
 
3473
        rp = erts_pid2proc_suspend(BIF_P, ERTS_PROC_LOCK_MAIN,
3210
3474
                                   BIF_ARG_1, ERTS_PROC_LOCK_MAIN);
3211
 
    if (!rp)
3212
 
        BIF_RET(am_false);
3213
 
    if (rp == ERTS_PROC_LOCK_BUSY)
3214
 
        ERTS_BIF_YIELD1(bif_export[BIF_garbage_collect_1], BIF_P, BIF_ARG_1);
 
3475
        if (rp == ERTS_PROC_LOCK_BUSY)
 
3476
            ERTS_BIF_YIELD1(bif_export[BIF_garbage_collect_1], BIF_P, BIF_ARG_1);
 
3477
#else
 
3478
        rp = erts_pid2proc(BIF_P, 0, BIF_ARG_1, 0);
 
3479
#endif
 
3480
        if (!rp)
 
3481
            BIF_RET(am_false);
 
3482
    }
3215
3483
 
3216
3484
    /* The GC cost is taken for the process executing this BIF. */
3217
3485
 
3218
3486
    FLAGS(rp) |= F_NEED_FULLSWEEP;
3219
3487
    reds = erts_garbage_collect(rp, 0, rp->arg_reg, rp->arity);
3220
3488
 
3221
 
    if (BIF_P != rp)
 
3489
#ifdef ERTS_SMP
 
3490
    if (BIF_P != rp) {
 
3491
        erts_resume(rp, ERTS_PROC_LOCK_MAIN);
3222
3492
        erts_smp_proc_unlock(rp, ERTS_PROC_LOCK_MAIN);
 
3493
    }
 
3494
#endif
3223
3495
 
3224
3496
    BIF_RET2(am_true, reds);
3225
3497
}
3261
3533
    Eterm* dead_ports;
3262
3534
    int alive, dead;
3263
3535
    Uint32 next_ss;
 
3536
    int i;
3264
3537
 
3265
3538
    /* To get a consistent snapshot... 
3266
3539
     * We add alive ports from start of the buffer
3269
3542
 
3270
3543
    erts_smp_mtx_lock(&ports_snapshot_mtx); /* One snapshot at a time */
3271
3544
 
3272
 
    erts_smp_atomic_set(&erts_dead_ports_ptr, (long) (port_buf + erts_max_ports));
3273
 
 
3274
 
    next_ss = erts_smp_atomic_inctest(&erts_ports_snapshot);
3275
 
 
3276
 
    if (erts_smp_atomic_read(&erts_ports_alive) > 0) {
3277
 
        long i;
3278
 
        for (i = erts_max_ports-1; i >= 0; i--) {
3279
 
            Port* prt = &erts_port[i];
3280
 
            erts_smp_port_state_lock(prt);
3281
 
            if (!(prt->status & ERTS_PORT_SFLGS_DEAD)
3282
 
                && prt->snapshot != next_ss) {
3283
 
                ASSERT(prt->snapshot == next_ss - 1);
3284
 
                *pp++ = prt->id;                
3285
 
                prt->snapshot = next_ss; /* Consumed by this snapshot */
3286
 
            }
3287
 
            erts_smp_port_state_unlock(prt);
 
3545
    erts_smp_atomic_set_nob(&erts_dead_ports_ptr,
 
3546
                            (erts_aint_t) (port_buf + erts_max_ports));
 
3547
 
 
3548
    next_ss = erts_smp_atomic32_inc_read_relb(&erts_ports_snapshot);
 
3549
 
 
3550
    for (i = erts_max_ports-1; i >= 0; i--) {
 
3551
        Port* prt = &erts_port[i];
 
3552
        erts_smp_port_state_lock(prt);
 
3553
        if (!(prt->status & ERTS_PORT_SFLGS_DEAD)
 
3554
            && prt->snapshot != next_ss) {
 
3555
            ASSERT(prt->snapshot == next_ss - 1);
 
3556
            *pp++ = prt->id;            
 
3557
            prt->snapshot = next_ss; /* Consumed by this snapshot */
3288
3558
        }
 
3559
        erts_smp_port_state_unlock(prt);
3289
3560
    }
3290
3561
 
3291
 
    dead_ports = (Eterm*)erts_smp_atomic_xchg(&erts_dead_ports_ptr,
3292
 
                                              (long)NULL);
 
3562
    dead_ports = (Eterm*)erts_smp_atomic_xchg_nob(&erts_dead_ports_ptr,
 
3563
                                                  (erts_aint_t) NULL);
3293
3564
    erts_smp_mtx_unlock(&ports_snapshot_mtx);
3294
3565
 
3295
3566
    ASSERT(pp <= dead_ports);
3300
3571
    ASSERT((alive+dead) <= erts_max_ports);
3301
3572
 
3302
3573
    if (alive+dead > 0) {
3303
 
        long i;
 
3574
        erts_aint_t i;
3304
3575
        Eterm *hp = HAlloc(BIF_P, (alive+dead)*2);
3305
3576
 
3306
3577
        for (i = 0; i < alive; i++) {
3350
3621
    erts_dsprintf_buf_t *dsbufp = erts_create_tmp_dsbuf(64);       
3351
3622
    pres = erts_dsprintf(dsbufp, "%.*T\n", INT_MAX, BIF_ARG_1);
3352
3623
    if (pres < 0)
3353
 
        erl_exit(1, "Failed to convert term to string: %d (s)\n",
 
3624
        erl_exit(1, "Failed to convert term to string: %d (%s)\n",
3354
3625
                 -pres, erl_errno_id(-pres));
3355
3626
    hp = HAlloc(BIF_P, 2*dsbufp->str_len); /* we need length * 2 heap words */
3356
3627
    res = buf_to_intlist(&hp, dsbufp->str, dsbufp->str_len, NIL);
3360
3631
}
3361
3632
 
3362
3633
 
3363
 
Eterm
3364
 
display_string_1(Process* p, Eterm string)
 
3634
BIF_RETTYPE display_string_1(BIF_ALIST_1)
3365
3635
{
 
3636
    Process* p = BIF_P;
 
3637
    Eterm string = BIF_ARG_1;
3366
3638
    int len = is_string(string);
3367
3639
    char *str;
3368
3640
 
3378
3650
    BIF_RET(am_true);
3379
3651
}
3380
3652
 
3381
 
Eterm
3382
 
display_nl_0(Process* p)
 
3653
BIF_RETTYPE display_nl_0(BIF_ALIST_0)
3383
3654
{
3384
3655
    erts_fprintf(stderr, "\n");
3385
3656
    BIF_RET(am_true);
3443
3714
 
3444
3715
/**********************************************************************/    
3445
3716
 
3446
 
BIF_RETTYPE is_builtin_3(Process* p, Eterm Mod, Eterm Name, Eterm Arity)
 
3717
BIF_RETTYPE is_builtin_3(BIF_ALIST_3)
3447
3718
{
 
3719
    Process* p = BIF_P;
 
3720
    Eterm Mod = BIF_ARG_1;
 
3721
    Eterm Name = BIF_ARG_2;
 
3722
    Eterm Arity = BIF_ARG_3;
 
3723
 
3448
3724
    if (is_not_atom(Mod) || is_not_atom(Name) || is_not_small(Arity)) {
3449
3725
        BIF_ERROR(p, BADARG);
3450
3726
    }
3468
3744
    erts_dsprintf_buf_t *dsbufp = erts_create_tmp_dsbuf(64);       
3469
3745
    pres = erts_dsprintf(dsbufp, "%T", term);
3470
3746
    if (pres < 0)
3471
 
        erl_exit(1, "Failed to convert term to list: %d (s)\n",
 
3747
        erl_exit(1, "Failed to convert term to list: %d (%s)\n",
3472
3748
                 -pres, erl_errno_id(-pres));
3473
3749
    hp = HAlloc(p, 2*dsbufp->str_len); /* we need length * 2 heap words */
3474
3750
    res = buf_to_intlist(&hp, dsbufp->str, dsbufp->str_len, NIL);
3509
3785
    BIF_RET(make_export(hp));
3510
3786
}
3511
3787
 
3512
 
Eterm
3513
 
fun_to_list_1(Process* p, Eterm fun)
 
3788
BIF_RETTYPE fun_to_list_1(BIF_ALIST_1)
3514
3789
{
 
3790
    Process* p = BIF_P;
 
3791
    Eterm fun = BIF_ARG_1;
 
3792
 
3515
3793
    if (is_not_any_fun(fun))
3516
3794
        BIF_ERROR(p, BADARG);
3517
3795
    BIF_RET(term2list_dsprintf(p, fun));
3796
4074
            goto error;
3797
4075
        }
3798
4076
        nval = (n > (Sint) ((Uint16) -1)) ? ((Uint16) -1) : ((Uint16) n);
3799
 
        oval = (Uint) erts_smp_atomic_xchg(&erts_max_gen_gcs, (long) nval);
 
4077
        oval = (Uint) erts_smp_atomic32_xchg_nob(&erts_max_gen_gcs,
 
4078
                                                 (erts_aint32_t) nval);
3800
4079
        BIF_RET(make_small(oval));
3801
4080
    } else if (BIF_ARG_1 == am_min_heap_size) {
3802
4081
        int oval = H_MIN_SIZE;
3806
4085
        }
3807
4086
 
3808
4087
        erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
3809
 
        erts_smp_block_system(0);
 
4088
        erts_smp_thr_progress_block();
3810
4089
 
3811
4090
        H_MIN_SIZE = erts_next_heap_size(n, 0);
3812
4091
 
3813
 
        erts_smp_release_system();
 
4092
        erts_smp_thr_progress_unblock();
3814
4093
        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
3815
4094
 
3816
4095
        BIF_RET(make_small(oval));
3822
4101
        }
3823
4102
 
3824
4103
        erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
3825
 
        erts_smp_block_system(0);
 
4104
        erts_smp_thr_progress_block();
3826
4105
 
3827
4106
        BIN_VH_MIN_SIZE = erts_next_heap_size(n, 0);
3828
4107
 
3829
 
        erts_smp_release_system();
 
4108
        erts_smp_thr_progress_unblock();
3830
4109
        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
3831
4110
 
3832
4111
        BIF_RET(make_small(oval));
3848
4127
        erts_backtrace_depth = n;
3849
4128
        BIF_RET(make_small(oval));
3850
4129
    } else if (BIF_ARG_1 == am_trace_control_word) {
3851
 
        BIF_RET(db_set_trace_control_word_1(BIF_P, BIF_ARG_2));
 
4130
        BIF_RET(db_set_trace_control_word(BIF_P, BIF_ARG_2));
3852
4131
    } else if (BIF_ARG_1 == am_sequential_tracer) {
3853
4132
        Eterm old_value = erts_set_system_seq_tracer(BIF_P,
3854
4133
                                                     ERTS_PROC_LOCK_MAIN,
3860
4139
        Uint i;
3861
4140
        ErlMessage* mp;
3862
4141
        erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
3863
 
        erts_smp_block_system(0);
 
4142
        erts_smp_thr_progress_block();
3864
4143
 
3865
4144
        for (i = 0; i < erts_max_processes; i++) {
3866
4145
            if (process_tab[i] != (Process*) 0) {
3877
4156
            }
3878
4157
        }
3879
4158
 
3880
 
        erts_smp_release_system();
 
4159
        erts_smp_thr_progress_unblock();
3881
4160
        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
3882
4161
 
3883
4162
        BIF_RET(am_true);
3900
4179
        if (is_value(res))
3901
4180
            BIF_RET(res);
3902
4181
    } else if (ERTS_IS_ATOM_STR("cpu_topology", BIF_ARG_1)) {
 
4182
        erts_send_warning_to_logger_str(
 
4183
            BIF_P->group_leader,
 
4184
            "A call to erlang:system_flag(cpu_topology, _) was made.\n"
 
4185
            "The cpu_topology argument is deprecated and scheduled\n"
 
4186
            "for removal in erts-5.10/OTP-R16. For more information\n"
 
4187
            "see the erlang:system_flag/2 documentation.\n");
3903
4188
        BIF_TRAP1(set_cpu_topology_trap, BIF_P, BIF_ARG_2);
3904
4189
    } else if (ERTS_IS_ATOM_STR("scheduler_bind_type", BIF_ARG_1)) {
 
4190
        erts_send_warning_to_logger_str(
 
4191
            BIF_P->group_leader,
 
4192
            "A call to erlang:system_flag(scheduler_bind_type, _) was\n"
 
4193
            "made. The scheduler_bind_type argument is deprecated and\n"
 
4194
            "scheduled for removal in erts-5.10/OTP-R16. For more\n"
 
4195
            "information see the erlang:system_flag/2 documentation.\n");
3905
4196
        return erts_bind_schedulers(BIF_P, BIF_ARG_2);
3906
4197
    }
3907
4198
    error:
4088
4379
erts_bif_prep_await_proc_exit_data_trap(Process *c_p, Eterm pid, Eterm ret)
4089
4380
{
4090
4381
    if (skip_current_msgq(c_p)) {
4091
 
        Eterm unused;
4092
 
        ERTS_BIF_PREP_TRAP3(unused, await_proc_exit_trap, c_p, pid, am_data, ret);
 
4382
        ERTS_BIF_PREP_TRAP3_NO_RET(await_proc_exit_trap, c_p, pid, am_data, ret);
4093
4383
    }
4094
4384
}
4095
4385
 
4097
4387
erts_bif_prep_await_proc_exit_reason_trap(Process *c_p, Eterm pid)
4098
4388
{
4099
4389
    if (skip_current_msgq(c_p)) {
4100
 
        Eterm unused;
4101
 
        ERTS_BIF_PREP_TRAP3(unused, await_proc_exit_trap, c_p,
 
4390
        ERTS_BIF_PREP_TRAP3_NO_RET(await_proc_exit_trap, c_p,
4102
4391
                            pid, am_reason, am_undefined);
4103
4392
    }
4104
4393
}
4113
4402
{
4114
4403
    ASSERT(is_atom(module) && is_atom(function));
4115
4404
    if (skip_current_msgq(c_p)) {
4116
 
        Eterm unused;
4117
4405
        Eterm term;
4118
4406
        Eterm *hp;
4119
4407
        int i;
4125
4413
            hp += 2;
4126
4414
        }
4127
4415
        term = TUPLE3(hp, module, function, term);
4128
 
        ERTS_BIF_PREP_TRAP3(unused, await_proc_exit_trap, c_p, pid, am_apply, term);
 
4416
        ERTS_BIF_PREP_TRAP3_NO_RET(await_proc_exit_trap, c_p, pid, am_apply, term);
4129
4417
    }
4130
4418
}
4131
4419
 
4139
4427
 
4140
4428
    erts_smp_spinlock_init(&make_ref_lock, "make_ref");
4141
4429
    erts_smp_mtx_init(&ports_snapshot_mtx, "ports_snapshot");
4142
 
    erts_smp_atomic_init(&erts_dead_ports_ptr, (long)NULL);
 
4430
    erts_smp_atomic_init_nob(&erts_dead_ports_ptr, (erts_aint_t) NULL);
4143
4431
 
4144
4432
    /*
4145
4433
     * bif_return_trap/1 is a hidden BIF that bifs that need to