~ubuntu-branches/ubuntu/karmic/erlang/karmic-security

« back to all changes in this revision

Viewing changes to lib/kernel/src/erts_debug.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%% ``The contents of this file are subject to the Erlang Public License,
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1999-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
2
7
%% Version 1.1, (the "License"); you may not use this file except in
3
8
%% compliance with the License. You should have received a copy of the
4
9
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
 
10
%% retrieved online at http://www.erlang.org/.
6
11
%% 
7
12
%% Software distributed under the License is distributed on an "AS IS"
8
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
14
%% the License for the specific language governing rights and limitations
10
15
%% under the License.
11
16
%% 
12
 
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
14
 
%% AB. All Rights Reserved.''
15
 
%% 
16
 
%%     $Id$
 
17
%% %CopyrightEnd%
17
18
%%
18
19
-module(erts_debug).
19
20
 
32
33
%%  counted once.  Example: If A = [a,b], B =[A,A] then size(B) returns 8,
33
34
%%  while flat_size(B) returns 12.
34
35
 
 
36
-spec size(term()) -> non_neg_integer().
 
37
 
35
38
size(Term) ->
36
39
    {Sum,_} = size(Term, gb_trees:empty(), 0),
37
40
    Sum.
76
79
            end
77
80
    end.
78
81
 
 
82
-spec is_term_seen(term(), [term()]) -> bool().
 
83
 
79
84
is_term_seen(Term, [H|T]) ->
80
85
    case erts_debug:same(Term, H) of
81
86
        true -> true;
83
88
    end;
84
89
is_term_seen(_, []) -> false.
85
90
 
86
 
%% df(Mod)               -- Disassemble Mod to file Mod.dis.
87
 
%% df(Mod, Func)         -- Disassemble Mod:Func/Any to file Mod_Func.dis.
88
 
%% df(Mod, Func, Arity)  -- Disassemble Mod:Func/Arity to file Mod_Func_Arity.dis.
 
91
%% df(Mod)              -- Disassemble Mod to file Mod.dis.
 
92
%% df(Mod, Func)        -- Disassemble Mod:Func/Any to file Mod_Func.dis.
 
93
%% df(Mod, Func, Arity) -- Disassemble Mod:Func/Arity to file Mod_Func_Arity.dis.
 
94
 
 
95
-type df_ret() :: 'ok' | {'error', {'badopen', module()}} | {'undef', module()}.
 
96
 
 
97
-spec df(module()) -> df_ret().
89
98
 
90
99
df(Mod) when is_atom(Mod) ->
91
 
    case catch Mod:module_info(functions) of
 
100
    try Mod:module_info(functions) of
92
101
        Fs0 when is_list(Fs0) ->
93
102
            Name = lists:concat([Mod, ".dis"]),
94
103
            Fs = [{Mod,Func,Arity} || {Func,Arity} <- Fs0],
95
 
            dff(Name, Fs);
96
 
        {'EXIT',_} ->
97
 
            {undef,Mod}
 
104
            dff(Name, Fs)
 
105
    catch _:_ -> {undef,Mod}
98
106
    end.
99
107
 
 
108
-spec df(module(), atom()) -> df_ret().
 
109
 
100
110
df(Mod, Func) when is_atom(Mod), is_atom(Func) ->
101
 
    case catch Mod:module_info(functions) of
 
111
    try Mod:module_info(functions) of
102
112
        Fs0 when is_list(Fs0) ->
103
 
            Name = lists:concat([Mod,"_",Func,".dis"]),
 
113
            Name = lists:concat([Mod, "_", Func, ".dis"]),
104
114
            Fs = [{Mod,Func1,Arity} || {Func1,Arity} <- Fs0, Func1 =:= Func],
105
 
            dff(Name, Fs);
106
 
        {'EXIT',_} ->
107
 
            {undef,Mod}
 
115
            dff(Name, Fs)
 
116
    catch _:_ -> {undef,Mod}
108
117
    end.
109
118
 
 
119
-spec df(module(), atom(), arity()) -> df_ret().
 
120
 
110
121
df(Mod, Func, Arity) when is_atom(Mod), is_atom(Func) ->
111
 
    case catch Mod:module_info(functions) of
 
122
    try Mod:module_info(functions) of
112
123
        Fs0 when is_list(Fs0) ->
113
 
            Name = lists:concat([Mod,"_",Func,"_",Arity,".dis"]),
 
124
            Name = lists:concat([Mod, "_", Func, "_", Arity, ".dis"]),
114
125
            Fs = [{Mod,Func1,Arity1} || {Func1,Arity1} <- Fs0,
115
126
                                        Func1 =:= Func, Arity1 =:= Arity],
116
 
            dff(Name, Fs);
117
 
        {'EXIT',_} ->
118
 
            {undef,Mod}
 
127
            dff(Name, Fs)
 
128
    catch _:_ -> {undef,Mod}
119
129
    end.
120
130
 
121
131
dff(File, Fs) when is_pid(File), is_list(Fs) ->