~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
44
44
#include "hipe_arch.h"
45
45
#endif
46
46
 
 
47
#ifdef ERTS_ENABLE_LOCK_COUNT
 
48
#include "erl_lock_count.h"
 
49
#endif
 
50
 
47
51
#ifdef VALGRIND
48
52
#include <valgrind/valgrind.h>
49
53
#include <valgrind/memcheck.h>
89
93
#ifdef ERTS_ENABLE_LOCK_CHECK
90
94
                                     " [lock-checking]"
91
95
#endif
 
96
#ifdef ERTS_ENABLE_LOCK_COUNT
 
97
                                     " [lock-counting]"
 
98
#endif
92
99
#ifdef PURIFY
93
100
                                     " [purify-compiled]"
94
101
#endif  
264
271
{
265
272
    return erts_print(to, arg, erts_system_version
266
273
#ifdef ERTS_SMP
267
 
                      , erts_no_of_schedulers
 
274
                      , erts_no_schedulers
268
275
#endif
269
276
#ifdef USE_THREADS
270
277
                      , erts_async_max_threads
643
650
     * If we are looking up another process and we need the main
644
651
     * lock we first do a try lock. If that fail, we do a lookup
645
652
     * with erts_pid2proc_not_running() instead. We may then have
646
 
     * to reschedule in order to wait for the other process to be
 
653
     * to yield in order to wait for the other process to be
647
654
     * scheduled out. When the other process has been scheduled
648
655
     * out we will be scheduled in again. This way the penalty is
649
656
     * only for the process doing the process_info, instead of
689
696
#define ERTS_PI_DEF_RES_ELEM_IX_BUF_SZ ERTS_PI_ARGS
690
697
 
691
698
static Eterm
692
 
process_info_list(Process *c_p, Eterm pid, Eterm list, int always_wrap)
 
699
process_info_list(Process *c_p, Eterm pid, Eterm list, int always_wrap,
 
700
                  int *yield)
693
701
{
694
702
    int def_res_elem_ix_buf[ERTS_PI_DEF_RES_ELEM_IX_BUF_SZ];
695
703
    int *res_elem_ix = &def_res_elem_ix_buf[0];
702
710
    int res_len, ix;
703
711
    Process *rp = NULL;
704
712
 
 
713
    *yield = 0;
 
714
 
705
715
    for (ix = 0; ix < ERTS_PI_ARGS; ix++)
706
716
        part_res[ix] = THE_NON_VALUE;
707
717
 
753
763
        res = am_undefined;
754
764
        goto done;
755
765
    }
 
766
    else if (rp == ERTS_PROC_LOCK_BUSY) {
 
767
        rp = NULL;
 
768
        res = THE_NON_VALUE;
 
769
        *yield = 1;
 
770
        goto done;
 
771
    }
756
772
 
757
773
    for (; res_elem_ix_ix >= 0; res_elem_ix_ix--) {
758
774
        ix = res_elem_ix[res_elem_ix_ix];
805
821
BIF_RETTYPE process_info_1(BIF_ALIST_1)
806
822
{
807
823
    Eterm res;
 
824
    int yield;
808
825
 
809
826
    if (is_external_pid(BIF_ARG_1)
810
827
        && external_pid_dist_entry(BIF_ARG_1) == erts_this_dist_entry)
815
832
        BIF_ERROR(BIF_P, BADARG);
816
833
    }
817
834
 
818
 
    res = process_info_list(BIF_P, BIF_ARG_1, pi_1_keys_list, 0);
819
 
    if (res == am_undefined)
820
 
        ERTS_SMP_BIF_CHK_RESCHEDULE(BIF_P);
821
 
    else if (is_non_value(res))
822
 
        BIF_ERROR(BIF_P, BADARG);
 
835
    res = process_info_list(BIF_P, BIF_ARG_1, pi_1_keys_list, 0, &yield);
 
836
    if (is_non_value(res)) {
 
837
        if (!yield)
 
838
            BIF_ERROR(BIF_P, BADARG);
 
839
        else
 
840
            ERTS_BIF_YIELD1(bif_export[BIF_process_info_1], BIF_P, BIF_ARG_1);
 
841
    }
823
842
 
824
843
    ASSERT(!(BIF_P->flags & F_P2PNR_RESCHED));
825
844
    BIF_RET(res);
832
851
    Process *rp;
833
852
    Eterm pid = BIF_ARG_1;
834
853
    ErtsProcLocks info_locks;
 
854
    int yield;
835
855
 
836
856
    if (is_external_pid(pid)
837
857
        && external_pid_dist_entry(pid) == erts_this_dist_entry)
846
866
        BIF_RET(NIL);
847
867
 
848
868
    if (is_list(BIF_ARG_2)) {
849
 
        res = process_info_list(BIF_P, BIF_ARG_1, BIF_ARG_2, 1);
850
 
        if (res == am_undefined)
851
 
            ERTS_SMP_BIF_CHK_RESCHEDULE(BIF_P);
852
 
        else if (is_non_value(res))
853
 
            BIF_ERROR(BIF_P, BADARG);
 
869
        res = process_info_list(BIF_P, BIF_ARG_1, BIF_ARG_2, 1, &yield);
 
870
        if (is_non_value(res)) {
 
871
            if (!yield)
 
872
                BIF_ERROR(BIF_P, BADARG);
 
873
            else
 
874
                ERTS_BIF_YIELD2(bif_export[BIF_process_info_2], BIF_P,
 
875
                                BIF_ARG_1, BIF_ARG_2);
 
876
        }
854
877
        ASSERT(!(BIF_P->flags & F_P2PNR_RESCHED));
855
878
        BIF_RET(res);
856
879
    }
861
884
    info_locks = pi_locks(BIF_ARG_2); 
862
885
 
863
886
    rp = pi_pid2proc(BIF_P, pid, info_locks);
864
 
    if (rp)
 
887
    if (!rp)
 
888
        res = am_undefined;
 
889
    else if (rp == ERTS_PROC_LOCK_BUSY)
 
890
        ERTS_BIF_YIELD2(bif_export[BIF_process_info_2], BIF_P,
 
891
                        BIF_ARG_1, BIF_ARG_2);
 
892
    else 
865
893
        res = process_info_aux(BIF_P, rp, pid, BIF_ARG_2, 0);
866
 
    else {
867
 
        ERTS_SMP_BIF_CHK_RESCHEDULE(BIF_P);
868
 
        res = am_undefined;
869
 
    }
870
894
    ASSERT(is_value(res));
871
895
 
872
896
#ifdef ERTS_SMP
1445
1469
        Eterm res;
1446
1470
        if (arity != 2)
1447
1471
            return am_badarg;
1448
 
        erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
1449
1472
        res = erts_memory(NULL, NULL, BIF_P, *tp);
1450
 
        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
1451
1473
        return res;
1452
1474
    } else if (sel == am_allocated) {
1453
1475
        if (arity == 2) {
1709
1731
        ASSERT(erts_compat_rel > 0);
1710
1732
        BIF_RET(make_small(erts_compat_rel));
1711
1733
    } else if (BIF_ARG_1 == am_memory) {
1712
 
        erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
1713
1734
        res = erts_memory(NULL, NULL, BIF_P, THE_NON_VALUE);
1714
 
        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
1715
1735
        BIF_RET(res);
1716
1736
    } else if (BIF_ARG_1 == am_multi_scheduling) {
1717
1737
#ifndef ERTS_SMP
1718
1738
        BIF_RET(am_disabled);
1719
1739
#else
1720
 
        if (erts_no_of_schedulers == 1)
 
1740
        if (erts_no_schedulers == 1)
1721
1741
            BIF_RET(am_disabled);
1722
1742
        else {
1723
1743
            BIF_RET(erts_is_multi_scheduling_blocked()
1726
1746
        }
1727
1747
#endif
1728
1748
    } else if (BIF_ARG_1 == am_allocated_areas) {
1729
 
        erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
1730
1749
        res = erts_allocated_areas(NULL, NULL, BIF_P);
1731
 
        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
1732
1750
        BIF_RET(res);
1733
1751
    } else if (BIF_ARG_1 == am_allocated) {
1734
1752
        BIF_RET(erts_instr_get_memory_map(BIF_P));
2152
2170
    } else if (ERTS_IS_ATOM_STR("constant_pool_support", BIF_ARG_1)) {
2153
2171
        BIF_RET(am_true);
2154
2172
    } else if (ERTS_IS_ATOM_STR("schedulers", BIF_ARG_1)) {
2155
 
        res = make_small(erts_no_of_schedulers);
 
2173
        res = make_small(erts_no_schedulers);
2156
2174
        BIF_RET(res);
2157
2175
    } else if (ERTS_IS_ATOM_STR("c_compiler_used", BIF_ARG_1)) {
2158
2176
        Eterm *hp = NULL;
2190
2208
#ifndef ERTS_SMP
2191
2209
        BIF_RET(NIL);
2192
2210
#else
2193
 
        if (erts_no_of_schedulers == 1)
 
2211
        if (erts_no_schedulers == 1)
2194
2212
            BIF_RET(NIL);
2195
2213
        else
2196
2214
            BIF_RET(erts_multi_scheduling_blockers(BIF_P));
2425
2443
#else
2426
2444
        if (prt->status & ERTS_PORT_SFLG_PORT_SPECIFIC_LOCK) {
2427
2445
            DECL_AM(port_level);
2428
 
            ASSERT(prt->drv_ptr->driver_flags
 
2446
            ASSERT(prt->drv_ptr->flags
2429
2447
                   & ERL_DRV_FLAG_USE_PORT_LOCKING);
2430
2448
            res = AM_port_level;
2431
2449
        }
2432
2450
        else {
2433
2451
            DECL_AM(driver_level);
2434
 
            ASSERT(!(prt->drv_ptr->driver_flags
 
2452
            ASSERT(!(prt->drv_ptr->flags
2435
2453
                     & ERL_DRV_FLAG_USE_PORT_LOCKING));
2436
2454
            res = AM_driver_level;
2437
2455
        }
2724
2742
            /* Used by (emulator) */
2725
2743
            int res;
2726
2744
#ifdef HAVE_ERTS_CHECK_IO_DEBUG
 
2745
            erts_smp_proc_unlock(BIF_P,ERTS_PROC_LOCK_MAIN);
2727
2746
            res = erts_check_io_debug();
 
2747
            erts_smp_proc_lock(BIF_P,ERTS_PROC_LOCK_MAIN);
2728
2748
#else
2729
2749
            res = 0;
2730
2750
#endif
3019
3039
                }
3020
3040
            }
3021
3041
        }
3022
 
        else if (ERTS_IS_ATOM_STR("slot_to_atom", BIF_ARG_1)) {
 
3042
        else if (ERTS_IS_ATOM_STR("colliding_names", BIF_ARG_1)) {
3023
3043
            /* Used by ets_SUITE (stdlib) */
3024
 
            Uint slot;
3025
 
            if (term_to_Uint(BIF_ARG_2, &slot) != 0) {
3026
 
                BIF_RET(erts_ets_slot_to_atom(slot));
 
3044
            if (is_tuple(BIF_ARG_2)) {
 
3045
                Eterm* tpl = tuple_val(BIF_ARG_2);
 
3046
                Uint cnt;
 
3047
                if (arityval(tpl[0]) == 2 && is_atom(tpl[1]) && 
 
3048
                    term_to_Uint(tpl[2], &cnt)) {
 
3049
                    BIF_RET(erts_ets_colliding_names(BIF_P,tpl[1],cnt));
 
3050
                }
3027
3051
            }
3028
3052
        }
3029
3053
        else if (ERTS_IS_ATOM_STR("re_loop_limit", BIF_ARG_1)) {
3037
3061
                BIF_RET(make_small(max_loops));
3038
3062
            }
3039
3063
        }
 
3064
        else if (ERTS_IS_ATOM_STR("unicode_loop_limit", BIF_ARG_1)) {
 
3065
            /* Used by unicode_SUITE (stdlib) */
 
3066
            Uint max_loops;
 
3067
            if (is_atom(BIF_ARG_2) && ERTS_IS_ATOM_STR("default", BIF_ARG_2)) {
 
3068
                max_loops = erts_unicode_set_loop_limit(-1);
 
3069
                BIF_RET(make_small(max_loops));
 
3070
            } else if (term_to_Uint(BIF_ARG_2, &max_loops) != 0) {
 
3071
                max_loops = erts_unicode_set_loop_limit(max_loops);
 
3072
                BIF_RET(make_small(max_loops));
 
3073
            }
 
3074
        }
3040
3075
        else if (ERTS_IS_ATOM_STR("hipe_test_reschedule_suspend", BIF_ARG_1)) {
3041
3076
            /* Used by hipe test suites */
3042
3077
            long flag = erts_smp_atomic_read(&hipe_test_reschedule_flag);
3043
3078
            if (!flag && BIF_ARG_2 != am_false) {
3044
3079
                erts_smp_atomic_set(&hipe_test_reschedule_flag, 1);
3045
3080
                erts_suspend(BIF_P, ERTS_PROC_LOCK_MAIN, NULL);
3046
 
                BIF_ERROR(BIF_P, RESCHEDULE);
 
3081
                ERTS_BIF_YIELD2(bif_export[BIF_erts_debug_set_internal_state_2],
 
3082
                                BIF_P, BIF_ARG_1, BIF_ARG_2);
3047
3083
            }
3048
3084
            erts_smp_atomic_set(&hipe_test_reschedule_flag, !flag);
3049
3085
            BIF_RET(NIL);
3072
3108
    BIF_ERROR(BIF_P, BADARG);
3073
3109
}
3074
3110
 
 
3111
#ifdef ERTS_ENABLE_LOCK_COUNT
 
3112
 
 
3113
static Eterm lcnt_build_lock_term(Process *p, erts_lcnt_lock_t *lock, Eterm res) {
 
3114
    Eterm loc, nlt, nlc, tup, lid, type;
 
3115
    Eterm ts, tns, tn, ttup;
 
3116
    Eterm* hp;
 
3117
    
 
3118
    unsigned long tries, colls;
 
3119
    char *ltype;
 
3120
    int need = 4 + 7 + 2;
 
3121
        
 
3122
 
 
3123
    ethr_atomic_read(&lock->tries, (long *)&tries);
 
3124
    ethr_atomic_read(&lock->colls, (long *)&colls);
 
3125
    need += (!IS_USMALL(0, tries) +
 
3126
             !IS_USMALL(0, colls) +
 
3127
             !IS_USMALL(0,lock->timer_s ) +
 
3128
             !IS_USMALL(0,lock->timer_ns) +
 
3129
             !IS_USMALL(0,lock->timer_n ))*BIG_UINT_HEAP_SIZE;
 
3130
    hp = HAlloc(p, need);
 
3131
    
 
3132
    ltype = erts_lcnt_lock_type(lock->flag);
 
3133
        
 
3134
    loc  = am_atom_put(lock->name, strlen(lock->name)); 
 
3135
    lid  = lock->id;                                    
 
3136
    type = am_atom_put(ltype, strlen(ltype));           
 
3137
    nlt  = erts_bld_uint( &hp, NULL, tries);             
 
3138
    nlc  = erts_bld_uint( &hp, NULL, colls);             
 
3139
 
 
3140
    ts   = erts_bld_uint( &hp, NULL, lock->timer_s);
 
3141
    tns  = erts_bld_uint( &hp, NULL, lock->timer_ns);
 
3142
    tn   = erts_bld_uint( &hp, NULL, lock->timer_n);
 
3143
    ttup = erts_bld_tuple(&hp, NULL, 3, 
 
3144
            ts, tns, tn);
 
3145
        
 
3146
    tup  = erts_bld_tuple(&hp, NULL, 6, 
 
3147
            loc, lid, type, nlt, nlc, ttup);  
 
3148
    
 
3149
    res  = erts_bld_cons( &hp, NULL, tup, res);          
 
3150
 
 
3151
    return res;
 
3152
}
 
3153
#endif
 
3154
 
 
3155
BIF_RETTYPE erts_debug_lock_counters_1(BIF_ALIST_1)
 
3156
{
 
3157
#ifdef ERTS_ENABLE_LOCK_COUNT
 
3158
    Eterm res = NIL;
 
3159
 
 
3160
    if (BIF_ARG_1 == am_info) {
 
3161
        erts_lcnt_lock_t *lock = NULL;
 
3162
        erts_lcnt_data_t *data; 
 
3163
 
 
3164
        /* block */
 
3165
        erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
3166
        erts_smp_block_system(0);
 
3167
 
 
3168
        data = erts_lcnt_get_data();
 
3169
        
 
3170
        /* Build eterm in the form of,
 
3171
         * * [{lock_name(), lock_id(), lock_type(), Tries :: int(), Colls :: int()}]
 
3172
         * */
 
3173
        for (lock = data->current_locks->head; lock != NULL ; lock = lock->next ) {
 
3174
            res = lcnt_build_lock_term(BIF_P, lock, res);
 
3175
        }
 
3176
        for (lock = data->deleted_locks->head; lock != NULL ; lock = lock->next ) {
 
3177
            res = lcnt_build_lock_term(BIF_P, lock, res);
 
3178
        }
 
3179
    
 
3180
        /* unblock */
 
3181
        erts_smp_release_system();
 
3182
        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
3183
        BIF_RET(res);
 
3184
    } else if (BIF_ARG_1 == am_clear) {
 
3185
        erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
3186
        erts_smp_block_system(0);
 
3187
        /* clear counters */
 
3188
        erts_lcnt_clear_counters();
 
3189
        erts_smp_release_system();
 
3190
        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
3191
        /* clear counters */
 
3192
        BIF_RET(am_ok);
 
3193
    }
 
3194
#endif /* ERTS_ENABLE_LOCK_COUNT */
 
3195
    BIF_ERROR(BIF_P, BADARG);
 
3196
}
 
3197
 
3075
3198
void
3076
3199
erts_bif_info_init(void)
3077
3200
{