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

« back to all changes in this revision

Viewing changes to erts/emulator/beam/bif.c

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

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
/*
2
2
 * %CopyrightBegin%
3
 
 * 
4
 
 * Copyright Ericsson AB 1996-2009. All Rights Reserved.
5
 
 * 
 
3
 *
 
4
 * Copyright Ericsson AB 1996-2011. All Rights Reserved.
 
5
 *
6
6
 * The contents of this file are subject to the Erlang Public License,
7
7
 * Version 1.1, (the "License"); you may not use this file except in
8
8
 * compliance with the License. You should have received a copy of the
9
9
 * Erlang Public License along with this software. If not, it can be
10
10
 * retrieved online at http://www.erlang.org/.
11
 
 * 
 
11
 *
12
12
 * Software distributed under the License is distributed on an "AS IS"
13
13
 * basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
 * the License for the specific language governing rights and limitations
15
15
 * under the License.
16
 
 * 
 
16
 *
17
17
 * %CopyrightEnd%
18
18
 */
19
19
 
616
616
    rp = erts_whereis_process(p, p_locks, target_name, ERTS_PROC_LOCK_LINK,
617
617
                              ERTS_P2P_FLG_ALLOW_OTHER_X);
618
618
    if (!rp) {
619
 
        Eterm lhp[3];
 
619
        DeclareTmpHeap(lhp,3,p);
620
620
        Eterm item;
 
621
        UseTmpHeap(3,p);
621
622
        erts_smp_proc_unlock(p, ERTS_PROC_LOCK_LINK);
622
623
        p_locks &= ~ERTS_PROC_LOCK_LINK;
623
624
        item = TUPLE2(lhp, target_name, erts_this_dist_entry->sysname);
624
625
        erts_queue_monitor_message(p, &p_locks,
625
626
                                   mon_ref, am_process, item, am_noproc);
 
627
        UnUseTmpHeap(3,p);
626
628
    }
627
629
    else if (rp != p) {
628
630
        erts_add_monitor(&(p->monitors), MON_ORIGIN, mon_ref, rp->id,
807
809
    /*
808
810
     * Store default values for options.
809
811
     */
810
 
    so.flags = SPO_USE_ARGS;
811
 
    so.min_heap_size = H_MIN_SIZE;
812
 
    so.priority = PRIORITY_NORMAL;
813
 
    so.max_gen_gcs = (Uint16) erts_smp_atomic_read(&erts_max_gen_gcs);
814
 
    so.scheduler = 0;
 
812
    so.flags          = SPO_USE_ARGS;
 
813
    so.min_heap_size  = H_MIN_SIZE;
 
814
    so.min_vheap_size = BIN_VH_MIN_SIZE;
 
815
    so.priority       = PRIORITY_NORMAL;
 
816
    so.max_gen_gcs    = (Uint16) erts_smp_atomic32_read(&erts_max_gen_gcs);
 
817
    so.scheduler      = 0;
815
818
 
816
819
    /*
817
820
     * Walk through the option list.
850
853
                } else {
851
854
                    so.min_heap_size = erts_next_heap_size(min_heap_size, 0);
852
855
                }
 
856
            } else if (arg == am_min_bin_vheap_size && is_small(val)) {
 
857
                Sint min_vheap_size = signed_val(val);
 
858
                if (min_vheap_size < 0) {
 
859
                    goto error;
 
860
                } else if (min_vheap_size < BIN_VH_MIN_SIZE) {
 
861
                    so.min_vheap_size = BIN_VH_MIN_SIZE;
 
862
                } else {
 
863
                    so.min_vheap_size = erts_next_heap_size(min_vheap_size, 0);
 
864
                }
853
865
            } else if (arg == am_fullsweep_after && is_small(val)) {
854
866
                Sint max_gen_gcs = signed_val(val);
855
867
                if (max_gen_gcs < 0) {
1079
1091
BIF_RETTYPE hibernate_3(BIF_ALIST_3)
1080
1092
{
1081
1093
    /*
1082
 
     * hibernate/3 is implemented as an instruction; therefore
1083
 
     * this function will never be called.
 
1094
     * hibernate/3 is usually translated to an instruction; therefore
 
1095
     * this function is only called from HiPE or when the call could not
 
1096
     * be translated.
1084
1097
     */
1085
 
    BIF_ERROR(BIF_P, BADARG);
 
1098
    Eterm reg[3];
 
1099
 
 
1100
    if (erts_hibernate(BIF_P, BIF_ARG_1, BIF_ARG_2, BIF_ARG_3, reg)) {
 
1101
        /*
 
1102
         * If hibernate succeeded, TRAP. The process will be suspended
 
1103
         * if status is P_WAITING or continue (if any message was in the queue).
 
1104
         */
 
1105
        BIF_TRAP_CODE_PTR_(BIF_P, BIF_P->i);
 
1106
    }
 
1107
    return THE_NON_VALUE;
1086
1108
}
1087
1109
 
1088
1110
/**********************************************************************/
1120
1142
}
1121
1143
 
1122
1144
/**********************************************************************/
 
1145
/*
 
1146
 * This is like exactly like error/1. The only difference is
 
1147
 * that Dialyzer thinks that it it will return an arbitrary term.
 
1148
 * It is useful in stub functions for NIFs.
 
1149
 */
 
1150
 
 
1151
BIF_RETTYPE nif_error_1(Process* p, Eterm term)
 
1152
{
 
1153
    p->fvalue = term;
 
1154
    BIF_ERROR(p, EXC_ERROR);
 
1155
}
 
1156
 
 
1157
/**********************************************************************/
 
1158
/*
 
1159
 * This is like exactly like error/2. The only difference is
 
1160
 * that Dialyzer thinks that it it will return an arbitrary term.
 
1161
 * It is useful in stub functions for NIFs.
 
1162
 */
 
1163
 
 
1164
BIF_RETTYPE nif_error_2(Process* p, Eterm value, Eterm args)
 
1165
{
 
1166
    Eterm* hp = HAlloc(p, 3);
 
1167
 
 
1168
    p->fvalue = TUPLE2(hp, value, args);
 
1169
    BIF_ERROR(p, EXC_ERROR_2);
 
1170
}
 
1171
 
 
1172
/**********************************************************************/
1123
1173
/* this is like throw/1 except that we set freason to EXC_EXIT */
1124
1174
 
1125
1175
BIF_RETTYPE exit_1(BIF_ALIST_1)
1311
1361
#ifdef ERTS_SMP
1312
1362
         if (rp == BIF_P)
1313
1363
             rp_locks &= ~ERTS_PROC_LOCK_MAIN;
1314
 
         else
 
1364
         if (rp_locks)
 
1365
             erts_smp_proc_unlock(rp, rp_locks);
 
1366
         if (rp != BIF_P)
1315
1367
             erts_smp_proc_dec_refc(rp);
1316
 
         erts_smp_proc_unlock(rp, rp_locks);
1317
1368
#endif
1318
1369
         /*
1319
1370
          * We may have exited ourselves and may have to take action.
1485
1536
       }
1486
1537
       BIF_RET(old_value);
1487
1538
   }
 
1539
   else if (BIF_ARG_1 == am_min_bin_vheap_size) {
 
1540
       Sint i;
 
1541
       if (!is_small(BIF_ARG_2)) {
 
1542
           goto error;
 
1543
       }
 
1544
       i = signed_val(BIF_ARG_2);
 
1545
       if (i < 0) {
 
1546
           goto error;
 
1547
       }
 
1548
       old_value = make_small(BIF_P->min_vheap_size);
 
1549
       if (i < BIN_VH_MIN_SIZE) {
 
1550
           BIF_P->min_vheap_size = BIN_VH_MIN_SIZE;
 
1551
       } else {
 
1552
           BIF_P->min_vheap_size = erts_next_heap_size(i, 0);
 
1553
       }
 
1554
       BIF_RET(old_value);
 
1555
   }
1488
1556
   else if (BIF_ARG_1 == am_sensitive) {
1489
1557
       Uint is_sensitive;
1490
1558
       if (BIF_ARG_2 == am_true) {
3212
3280
 
3213
3281
    erts_smp_mtx_lock(&ports_snapshot_mtx); /* One snapshot at a time */
3214
3282
 
3215
 
    erts_smp_atomic_set(&erts_dead_ports_ptr, (long) (port_buf + erts_max_ports));
 
3283
    erts_smp_atomic_set(&erts_dead_ports_ptr,
 
3284
                        (erts_aint_t) (port_buf + erts_max_ports));
3216
3285
 
3217
3286
    next_ss = erts_smp_atomic_inctest(&erts_ports_snapshot);
3218
3287
 
3219
3288
    if (erts_smp_atomic_read(&erts_ports_alive) > 0) {
3220
 
        long i;
 
3289
        erts_aint_t i;
3221
3290
        for (i = erts_max_ports-1; i >= 0; i--) {
3222
3291
            Port* prt = &erts_port[i];
3223
3292
            erts_smp_port_state_lock(prt);
3232
3301
    }
3233
3302
 
3234
3303
    dead_ports = (Eterm*)erts_smp_atomic_xchg(&erts_dead_ports_ptr,
3235
 
                                              (long)NULL);
 
3304
                                              (erts_aint_t) NULL);
3236
3305
    erts_smp_mtx_unlock(&ports_snapshot_mtx);
3237
3306
 
3238
3307
    ASSERT(pp <= dead_ports);
3243
3312
    ASSERT((alive+dead) <= erts_max_ports);
3244
3313
 
3245
3314
    if (alive+dead > 0) {
3246
 
        long i;
 
3315
        erts_aint_t i;
3247
3316
        Eterm *hp = HAlloc(BIF_P, (alive+dead)*2);
3248
3317
 
3249
3318
        for (i = 0; i < alive; i++) {
3439
3508
    if (arity < 0) {
3440
3509
        goto error;
3441
3510
    }
 
3511
#if HALFWORD_HEAP
 
3512
    hp = HAlloc(BIF_P, 3);
 
3513
    hp[0] = HEADER_EXPORT;
 
3514
    /* Yes, May be misaligned, but X86_64 will fix it... */
 
3515
    *((Export **) (hp+1)) = erts_export_get_or_make_stub(BIF_ARG_1, BIF_ARG_2, (Uint) arity);
 
3516
#else
3442
3517
    hp = HAlloc(BIF_P, 2);
3443
3518
    hp[0] = HEADER_EXPORT;
3444
3519
    hp[1] = (Eterm) erts_export_get_or_make_stub(BIF_ARG_1, BIF_ARG_2, (Uint) arity);
 
3520
#endif
3445
3521
    BIF_RET(make_export(hp));
3446
3522
}
3447
3523
 
3547
3623
 
3548
3624
      etp = (ExternalThing *) HAlloc(BIF_P, EXTERNAL_THING_HEAD_SIZE + 1);
3549
3625
      etp->header = make_external_pid_header(1);
3550
 
      etp->next = MSO(BIF_P).externals;
 
3626
      etp->next = MSO(BIF_P).first;
3551
3627
      etp->node = enp;
3552
3628
      etp->data.ui[0] = make_pid_data(c, b);
3553
3629
 
3554
 
      MSO(BIF_P).externals = etp;
 
3630
      MSO(BIF_P).first = (struct erl_off_heap_header*) etp;
3555
3631
      erts_deref_dist_entry(dep);
3556
3632
      BIF_RET(make_external_pid(etp));
3557
3633
    }
3732
3808
            goto error;
3733
3809
        }
3734
3810
        nval = (n > (Sint) ((Uint16) -1)) ? ((Uint16) -1) : ((Uint16) n);
3735
 
        oval = (Uint) erts_smp_atomic_xchg(&erts_max_gen_gcs, (long) nval);
 
3811
        oval = (Uint) erts_smp_atomic32_xchg(&erts_max_gen_gcs,
 
3812
                                             (erts_aint32_t) nval);
3736
3813
        BIF_RET(make_small(oval));
3737
3814
    } else if (BIF_ARG_1 == am_min_heap_size) {
3738
3815
        int oval = H_MIN_SIZE;
 
3816
 
3739
3817
        if (!is_small(BIF_ARG_2) || (n = signed_val(BIF_ARG_2)) < 0) {
3740
3818
            goto error;
3741
3819
        }
 
3820
 
 
3821
        erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
3822
        erts_smp_block_system(0);
 
3823
 
3742
3824
        H_MIN_SIZE = erts_next_heap_size(n, 0);
 
3825
 
 
3826
        erts_smp_release_system();
 
3827
        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
3828
 
 
3829
        BIF_RET(make_small(oval));
 
3830
    } else if (BIF_ARG_1 == am_min_bin_vheap_size) {
 
3831
        int oval = BIN_VH_MIN_SIZE;
 
3832
 
 
3833
        if (!is_small(BIF_ARG_2) || (n = signed_val(BIF_ARG_2)) < 0) {
 
3834
            goto error;
 
3835
        }
 
3836
 
 
3837
        erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
3838
        erts_smp_block_system(0);
 
3839
 
 
3840
        BIN_VH_MIN_SIZE = erts_next_heap_size(n, 0);
 
3841
 
 
3842
        erts_smp_release_system();
 
3843
        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
3844
 
3743
3845
        BIF_RET(make_small(oval));
3744
3846
    } else if (BIF_ARG_1 == am_display_items) {
3745
3847
        int oval = display_items;
3832
3934
    if ((range = signed_val(BIF_ARG_2)) <= 0) {  /* [1..MAX_SMALL] */
3833
3935
        BIF_ERROR(BIF_P, BADARG);
3834
3936
    }
3835
 
#ifdef ARCH_64
 
3937
#if defined(ARCH_64) && !HALFWORD_HEAP
3836
3938
    if (range > ((1L << 27) - 1))
3837
3939
        BIF_ERROR(BIF_P, BADARG);
3838
3940
#endif
3904
4006
    /*
3905
4007
     * Return either a small or a big. Use the heap for bigs if there is room.
3906
4008
     */
3907
 
#ifdef ARCH_64
 
4009
#if defined(ARCH_64) && !HALFWORD_HEAP
3908
4010
    BIF_RET(make_small(final_hash));
3909
4011
#else
3910
4012
    if (IS_USMALL(0, final_hash)) {
4050
4152
 
4051
4153
    erts_smp_spinlock_init(&make_ref_lock, "make_ref");
4052
4154
    erts_smp_mtx_init(&ports_snapshot_mtx, "ports_snapshot");
4053
 
    erts_smp_atomic_init(&erts_dead_ports_ptr, (long)NULL);
 
4155
    erts_smp_atomic_init(&erts_dead_ports_ptr, (erts_aint_t) NULL);
4054
4156
 
4055
4157
    /*
4056
4158
     * bif_return_trap/1 is a hidden BIF that bifs that need to
4066
4168
#else
4067
4169
    bif_return_trap_export.code[2] = 1;
4068
4170
#endif
4069
 
    bif_return_trap_export.code[3] = (Eterm) em_apply_bif;
4070
 
    bif_return_trap_export.code[4] = (Eterm) &bif_return_trap;
 
4171
    bif_return_trap_export.code[3] = (BeamInstr) em_apply_bif;
 
4172
    bif_return_trap_export.code[4] = (BeamInstr) &bif_return_trap;
4071
4173
 
4072
4174
    flush_monitor_message_trap = erts_export_put(am_erlang,
4073
4175
                                                 am_flush_monitor_message,
4082
4184
    await_proc_exit_trap = erts_export_put(am_erlang,am_await_proc_exit,3);
4083
4185
}
4084
4186
 
4085
 
BIF_RETTYPE blocking_read_file_1(BIF_ALIST_1)
4086
 
{
4087
 
    Eterm bin;
4088
 
    Eterm* hp;
4089
 
    byte *buff;
4090
 
    int i, buff_size;
4091
 
    FILE *file;
4092
 
    struct stat file_info;
4093
 
    char *filename = NULL;
4094
 
 
4095
 
    i = list_length(BIF_ARG_1);
4096
 
    if (i < 0) {
4097
 
        BIF_ERROR(BIF_P, BADARG);
4098
 
    }
4099
 
    filename = erts_alloc(ERTS_ALC_T_TMP, i + 1);
4100
 
    if (intlist_to_buf(BIF_ARG_1, filename, i) != i)
4101
 
        erl_exit(1, "%s:%d: Internal error\n", __FILE__, __LINE__);
4102
 
    filename[i] = '\0';
4103
 
 
4104
 
    hp = HAlloc(BIF_P, 3);
4105
 
 
4106
 
    file = fopen(filename, "r");
4107
 
    if(file == NULL){
4108
 
        erts_free(ERTS_ALC_T_TMP, (void *) filename);
4109
 
        BIF_RET(TUPLE2(hp, am_error, am_nofile));
4110
 
    }
4111
 
 
4112
 
    stat(filename, &file_info);
4113
 
    erts_free(ERTS_ALC_T_TMP, (void *) filename);
4114
 
 
4115
 
    buff_size = file_info.st_size;
4116
 
    buff = (byte *) erts_alloc_fnf(ERTS_ALC_T_TMP, buff_size);
4117
 
    if (!buff) {
4118
 
        fclose(file);
4119
 
        BIF_RET(TUPLE2(hp, am_error, am_allocator));
4120
 
    }
4121
 
    fread(buff, 1, buff_size, file);
4122
 
    fclose(file);
4123
 
    bin = new_binary(BIF_P, buff, buff_size);
4124
 
    erts_free(ERTS_ALC_T_TMP, (void *) buff);
4125
 
 
4126
 
    BIF_RET(TUPLE2(hp, am_ok, bin));
4127
 
}
4128
4187
#ifdef HARDDEBUG
4129
4188
/*
4130
4189
You'll need this line in bif.tab to be able to use this debug bif