~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

Viewing changes to lib/compiler/src/beam_disasm.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-12-20 09:03:40 UTC
  • mto: (3.6.1 sid)
  • mto: This revision was merged to the branch mainline in revision 27.
  • Revision ID: james.westby@ubuntu.com-20091220090340-w3kbi1lj1wp7l2m3
Tags: upstream-13.b.3-dfsg
ImportĀ upstreamĀ versionĀ 13.b.3-dfsg

Show diffs side-by-side

added added

removed removed

Lines of Context:
24
24
 
25
25
-module(beam_disasm).
26
26
 
27
 
-export([file/1]). %% the main function and some utilities below
28
 
-export([dfs/1, df/1, files/1, pp/1, pp/2, format_error/1]).
29
 
-export([function__code/1]).
 
27
-export([file/1]). %% the main function
 
28
-export([function__code/1, format_error/1]).
 
29
-ifdef(DEBUG_DISASM).
 
30
-export([dfs/1, df/1, files/1, pp/1, pp/2]).
 
31
-endif.
30
32
 
31
33
-author("Kostis Sagonas").
32
34
 
52
54
%%-----------------------------------------------------------------------
53
55
 
54
56
%% -spec function__name(#function{}) -> atom().
55
 
%% function__name(#function{name=N}) -> N.
 
57
%% function__name(#function{name = N}) -> N.
56
58
%% -spec function__arity(#function{}) -> arity().
57
 
%% function__arity(#function{arity=A}) -> A.
58
 
%% function__entry(#function{entry=E}) -> E.
 
59
%% function__arity(#function{arity = A}) -> A.
 
60
%% function__entry(#function{entry = E}) -> E.
59
61
 
60
62
-spec function__code(#function{}) -> [beam_instr()].
61
 
function__code(#function{code=Code}) -> Code.
 
63
function__code(#function{code = Code}) -> Code.
62
64
 
63
65
-spec function__code_update(#function{}, [beam_instr()]) -> #function{}.
64
66
function__code_update(Function, NewCode) ->
67
69
%%-----------------------------------------------------------------------
68
70
%% Error information
69
71
 
70
 
-spec format_error({'internal',_} | {'error',atom(),_}) -> string().
 
72
-spec format_error({'internal',term()} | {'error',atom(),term()}) -> string().
71
73
 
72
74
format_error({internal,Error}) ->
73
75
    io_lib:format("~p: disassembly failed with reason ~P.",
80
82
%% stream, pretty-printed, and to just pretty-print, also commented.
81
83
%%-----------------------------------------------------------------------
82
84
 
 
85
-ifdef(DEBUG_DISASM).
 
86
 
83
87
dfs(Files) when is_list(Files) ->
84
88
    lists:foreach(fun df/1, Files).
85
89
 
98
102
 
99
103
file(File, Dest) ->
100
104
    case file(File) of
101
 
        #beam_file{code=DisasmCode} ->
102
 
            pp(Dest, [{file,File},{code,DisasmCode}]);
 
105
        #beam_file{code = DisasmCode} ->
 
106
            pp(Dest, [{file,File}, {code,DisasmCode}]);
103
107
        Error -> Error
104
108
    end.
105
109
 
108
112
pp(Disasm) ->
109
113
    pp(group_leader(), Disasm).
110
114
 
111
 
-spec pp(pid() | string(), [_]) -> 'ok' | {'error', atom()}.
 
115
-spec pp(pid() | file:filename(), [_]) -> 'ok' | {'error', atom()}.
112
116
 
113
117
pp(Stream, Disasm) when is_pid(Stream), is_list(Disasm) ->
114
118
    NL = io_lib:nl(),
145
149
pp_instr(I) ->
146
150
    io_lib:format("    ~p.", [I]).
147
151
 
 
152
-endif.
 
153
 
148
154
%%-----------------------------------------------------------------------
149
155
%% The main exported function
150
156
%%   File is either a file name or a binary containing the code.
151
157
%%   Call `format_error({error, Module, Reason})' for an error string.
152
158
%%-----------------------------------------------------------------------
153
159
 
154
 
-spec file(string() | binary()) -> #beam_file{} | {'error',atom(),_}.
 
160
-spec file(file:filename() | binary()) -> #beam_file{} | {'error',atom(),_}.
155
161
 
156
162
file(File) ->
157
163
    try process_chunks(File)
183
189
                    CompInfoBin when is_binary(CompInfoBin) ->
184
190
                        binary_to_term(CompInfoBin)
185
191
                end,
186
 
            #beam_file{module=Module,
187
 
                       exports=Exports,
188
 
                       attributes=Attributes,
189
 
                       comp_info=CompInfo,
190
 
                       code=Code};
 
192
            #beam_file{module = Module,
 
193
                       labeled_exports = Exports,
 
194
                       attributes = Attributes,
 
195
                       compile_info = CompInfo,
 
196
                       code = Code};
191
197
        Error -> Error
192
198
    end.
193
199
 
1084
1090
    {I,Lbl,decode_field_flags(U),A3};
1085
1091
 
1086
1092
%%
 
1093
%% R13B03.
 
1094
%%
 
1095
resolve_inst({on_load,[]},_,_,_) ->
 
1096
    on_load;
 
1097
 
 
1098
%%
1087
1099
%% Catches instructions that are not yet handled.
1088
1100
%%
1089
1101
resolve_inst(X,_,_,_) -> ?exit({resolve_inst,X}).