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

« 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-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:
25
25
 
26
26
%%-----------------------------------------------------------------------
27
27
 
28
 
%% -type(gb_tree()      :: tuple()).  % XXX: temporarily
 
28
%% -type gb_tree()      :: tuple().  % XXX: temporarily
29
29
 
30
 
%% -type(literals()     :: 'none' | gb_tree()).
31
 
-type(symbolic_tag() :: 'a' | 'f' | 'h' | 'i' | 'u' | 'x' | 'y' | 'z').
32
 
%% -type(disasm_tag() :: symbolic_tag() | 'fr' | 'atom' | 'float' | 'literal').
33
 
%% -type(disasm_term()  :: 'nil' | {disasm_tag(), _}).
 
30
%% -type literals()     :: 'none' | gb_tree().
 
31
-type symbolic_tag() :: 'a' | 'f' | 'h' | 'i' | 'u' | 'x' | 'y' | 'z'.
 
32
%% -type disasm_tag() :: symbolic_tag() | 'fr' | 'atom' | 'float' | 'literal'.
 
33
%% -type disasm_term()  :: 'nil' | {disasm_tag(), _}.
34
34
 
35
35
%%-----------------------------------------------------------------------
36
36
 
43
43
%% them when/if they get used in other files.)
44
44
%%-----------------------------------------------------------------------
45
45
 
46
 
%% -spec(function__name/1 :: (#function{}) -> atom()).
 
46
%% -spec function__name(#function{}) -> atom().
47
47
%% function__name(#function{name=N}) -> N.
48
 
%% -spec(function__arity/1 :: (#function{}) -> byte()).
 
48
%% -spec function__arity(#function{}) -> byte().
49
49
%% function__arity(#function{arity=A}) -> A.
50
50
%% function__entry(#function{entry=E}) -> E.
51
51
 
52
 
-spec(function__code/1 :: (#function{}) -> [beam_instr()]).
 
52
-spec function__code(#function{}) -> [beam_instr()].
53
53
function__code(#function{code=Code}) -> Code.
54
54
 
55
 
-spec(function__code_update/2 :: (#function{}, [beam_instr()]) -> #function{}).
 
55
-spec function__code_update(#function{}, [beam_instr()]) -> #function{}.
56
56
function__code_update(Function, NewCode) ->
57
57
  Function#function{code = NewCode}.
58
58
 
59
59
%%-----------------------------------------------------------------------
60
60
%% Error information
61
61
 
62
 
-spec(format_error/1 :: ({'internal',_} | {'error',atom(),_}) -> string()).
 
62
-spec format_error({'internal',_} | {'error',atom(),_}) -> string().
63
63
 
64
64
format_error({internal,Error}) ->
65
65
    io_lib:format("~p: disassembly failed with reason ~P.",
95
95
        Error -> Error
96
96
    end.
97
97
 
98
 
-spec(pp/1 :: ([_]) -> 'ok' | {'error','file',atom()}).
 
98
-spec pp([_]) -> 'ok' | {'error','file',atom()}.
99
99
 
100
100
pp(Disasm) ->
101
101
    pp(group_leader(), Disasm).
102
102
 
103
 
-spec(pp/2 :: (pid() | string(), [_]) -> 'ok' | {'error','file',atom()}).
 
103
-spec pp(pid() | string(), [_]) -> 'ok' | {'error','file',atom()}.
104
104
 
105
105
pp(Stream, Disasm) when is_pid(Stream), is_list(Disasm) ->
106
106
    NL = io_lib:nl(),
143
143
%%   Call `format_error({error, Module, Reason})' for an error string.
144
144
%%-----------------------------------------------------------------------
145
145
 
146
 
-spec(file/1 :: (string() | binary()) -> #beam_file{} | {'error',atom(),_}).
 
146
-spec file(string() | binary()) -> #beam_file{} | {'error',atom(),_}.
147
147
 
148
148
file(File) ->
149
149
    try process_chunks(File)
197
197
%% Disassembles the lambda (fun) table of a BEAM file.
198
198
%%-----------------------------------------------------------------------
199
199
 
200
 
%-type(lambda_info() :: {non_neg_integer(), tuple()}).
201
 
%-spec(beam_disasm_lambdas/2 ::
202
 
%      ('none' | binary(), gb_tree()) -> 'none' | [lambda_info()]).
 
200
%% -type lambda_info() :: {non_neg_integer(), tuple()}.
 
201
%% -spec beam_disasm_lambdas('none' | binary(), gb_tree()) -> 'none' | [lambda_info()].
203
202
beam_disasm_lambdas(none, _) -> none;
204
203
beam_disasm_lambdas(<<_:32,Tab/binary>>, Atoms) ->
205
204
    disasm_lambdas(Tab, Atoms, 0).
214
213
%% Disassembles the literal table (constant pool) of a BEAM file.
215
214
%%-----------------------------------------------------------------------
216
215
 
217
 
%% -spec(beam_disasm_literals/1 :: ('none' | binary()) -> literals()).
 
216
%% -spec beam_disasm_literals('none' | binary()) -> literals().
218
217
beam_disasm_literals(none) -> none;
219
218
beam_disasm_literals(<<_:32,Compressed/binary>>) ->
220
219
    <<_:32,Tab/binary>> = zlib:uncompress(Compressed),
237
236
                  CodeBin/binary>>, Atoms, Imports,
238
237
                 Str, Lambdas, Literals, M) ->
239
238
    Code = binary_to_list(CodeBin),
240
 
    case catch disasm_code(Code, Atoms, Literals) of
241
 
        {'EXIT',Rsn} ->
242
 
            ?NO_DEBUG('code disasm failed: ~p~n',[Rsn]),
243
 
            ?exit(Rsn);
 
239
    try disasm_code(Code, Atoms, Literals) of
244
240
        DisasmCode ->
245
241
            Functions = get_function_chunks(DisasmCode),
246
242
            Labels = mk_labels(local_labels(Functions)),
248
244
                                   resolve_names(Is, Imports, Str,
249
245
                                                 Labels, Lambdas, Literals, M))
250
246
             || Function = #function{code=Is} <- Functions]
 
247
    catch
 
248
        error:Rsn ->
 
249
            ?NO_DEBUG('code disassembling failed: ~p~n',[Rsn]),
 
250
            ?exit(Rsn)
251
251
    end.
252
252
 
253
253
%%-----------------------------------------------------------------------
340
340
%%-----------------------------------------------------------------------
341
341
 
342
342
disasm_instr(B, Bs, Atoms, Literals) ->
343
 
    {SymOp,Arity} = beam_opcodes:opname(B),
 
343
    {SymOp, Arity} = beam_opcodes:opname(B),
344
344
    case SymOp of
345
345
        select_val ->
346
346
            disasm_select_inst(select_val, Bs, Atoms, Literals);
347
347
        select_tuple_arity ->
348
348
            disasm_select_inst(select_tuple_arity, Bs, Atoms, Literals);
349
349
        _ ->
350
 
            case catch decode_n_args(Arity, Bs, Atoms, Literals) of
351
 
                {'EXIT',Rsn} ->
352
 
                    ?NO_DEBUG("decode_n_args(~p,~p) failed~n",[Arity,Bs]),
353
 
                    {{'EXIT',{SymOp,Arity,Rsn}},[]};
354
 
                {Args,RestBs} ->
355
 
                    ?NO_DEBUG("instr ~p~n",[{SymOp,Args}]),
356
 
                    {{SymOp,Args}, RestBs}
 
350
            try decode_n_args(Arity, Bs, Atoms, Literals) of
 
351
                {Args, RestBs} ->
 
352
                    ?NO_DEBUG("instr ~p~n", [{SymOp, Args}]),
 
353
                    {{SymOp, Args}, RestBs}
 
354
            catch
 
355
                error:Rsn ->
 
356
                    ?NO_DEBUG("decode_n_args(~p,~p) failed~n", [Arity, Bs]),
 
357
                    ?exit({cannot_disasm_instr, {SymOp, Arity, Rsn}})
357
358
            end
358
359
    end.
359
360
 
376
377
    {{Inst,[X,F,{Z,U,List}]},RestBs}.
377
378
 
378
379
%%-----------------------------------------------------------------------
379
 
%% decode_arg([Byte]) -> { Arg, [Byte] }
 
380
%% decode_arg([Byte]) -> {Arg, [Byte]}
380
381
%%
381
382
%% - an arg can have variable length, so we must return arg + remaining bytes
382
383
%% - decodes an argument into its 'raw' form: { Tag, Value }
384
385
%%   assign a type to it
385
386
%%-----------------------------------------------------------------------
386
387
 
387
 
%% -spec(decode_arg/1 :: ([byte(),...]) -> {{disasm_tag(),_}, [byte()]}).
 
388
%% -spec decode_arg([byte(),...]) -> {{disasm_tag(),_}, [byte()]}.
388
389
decode_arg([B|Bs]) ->
389
390
    Tag = decode_tag(B band 2#111),
390
391
    ?NO_DEBUG('Tag = ~p, B = ~p, Bs = ~p~n',[Tag,B,Bs]),
396
397
            decode_int(Tag, B, Bs)
397
398
    end.
398
399
 
399
 
%% -spec(decode_arg/3 ::
400
 
%%      ([byte(),...], gb_tree(), literals()) -> {disasm_term(), [byte()]}).
 
400
%% -spec decode_arg([byte(),...], gb_tree(), literals()) ->
 
401
%%              {disasm_term(), [byte()]}).
401
402
decode_arg([B|Bs0], Atoms, Literals) ->
402
403
    Tag = decode_tag(B band 2#111),
403
404
    ?NO_DEBUG('Tag = ~p, B = ~p, Bs = ~p~n',[Tag,B,Bs]),
451
452
    ?NO_DEBUG('Len = ~p, IntBs = ~p, Num = ~p~n', [Len,IntBs,Num]),
452
453
    {{Tag,Num},RemBs}.
453
454
 
454
 
-spec(decode_int_length/2 :: (integer(), [byte()]) -> {integer(), [byte()]}).
 
455
-spec decode_int_length(integer(), [byte()]) -> {integer(), [byte()]}.
455
456
decode_int_length(B, Bs) ->
456
457
    %% The following imitates get_erlang_integer() in beam_load.c
457
458
    %% Len is the size of the integer value in bytes
468
469
            {L+2,Bs}
469
470
    end.
470
471
    
471
 
-spec(decode_negative/2 ::
472
 
      (non_neg_integer(), non_neg_integer()) -> neg_integer()).
 
472
-spec decode_negative(non_neg_integer(), non_neg_integer()) -> neg_integer().
473
473
decode_negative(N, Len) ->
474
474
    N - (1 bsl (Len*8)). % 8 is number of bits in a byte
475
475
 
497
497
decode_z_tagged(_,B,_,_) ->
498
498
    ?exit({decode_z_tagged,{weird_value,B}}).
499
499
 
500
 
-spec(decode_float/1 :: ([byte(),...]) -> {{'float',float()}, [byte()]}).
 
500
-spec decode_float([byte(),...]) -> {{'float',float()}, [byte()]}.
501
501
decode_float(Bs) ->
502
502
    {FL,RestBs} = take_bytes(8,Bs),
503
503
    <<Float:64/float>> = list_to_binary(FL),
504
504
    {{float,Float},RestBs}.
505
505
 
506
 
-spec(decode_fr/1 :: ([byte(),...]) -> {{'fr',non_neg_integer()}, [byte()]}).
 
506
-spec decode_fr([byte(),...]) -> {{'fr',non_neg_integer()}, [byte()]}.
507
507
decode_fr(Bs) ->
508
508
    {{u,Fr},RestBs} = decode_arg(Bs),
509
509
    {{fr,Fr},RestBs}.
528
528
%% take N bytes from a stream, return {Taken_bytes, Remaining_bytes}
529
529
%%-----------------------------------------------------------------------
530
530
 
531
 
-spec(take_bytes/2 :: (non_neg_integer(), [byte()]) -> {[byte()],[byte()]}).
 
531
-spec take_bytes(non_neg_integer(), [byte()]) -> {[byte()],[byte()]}.
532
532
take_bytes(N, Bs) ->
533
533
    take_bytes(N, Bs, []).
534
534
 
567
567
%% Convert a numeric tag value into a symbolic one
568
568
%%-----------------------------------------------------------------------
569
569
 
570
 
-spec(decode_tag/1 :: (0..7) -> symbolic_tag()).
 
570
-spec decode_tag(0..7) -> symbolic_tag().
571
571
decode_tag(?tag_u) -> u;
572
572
decode_tag(?tag_i) -> i;
573
573
decode_tag(?tag_a) -> a;
1045
1045
    {bs_init_bits,Lbl,A2,W,R,decode_field_flags(F),A6};
1046
1046
 
1047
1047
%%
 
1048
%% R12B-5.
 
1049
%%
 
1050
resolve_inst({bs_get_utf8=I,[Lbl,Arg2,Arg3,{u,U},Arg4]},_,_,_) ->
 
1051
    [A2,A3,A4] = resolve_args([Arg2,Arg3,Arg4]),
 
1052
    {test,I,Lbl,[A2,A3,decode_field_flags(U),A4]};
 
1053
resolve_inst({bs_skip_utf8=I,[Lbl,Arg2,Arg3,{u,U}]},_,_,_) ->
 
1054
    [A2,A3] = resolve_args([Arg2,Arg3]),
 
1055
    {test,I,Lbl,[A2,A3,decode_field_flags(U)]};
 
1056
resolve_inst({bs_get_utf16=I,[Lbl,Arg2,Arg3,{u,U},Arg4]},_,_,_) ->
 
1057
    [A2,A3,A4] = resolve_args([Arg2,Arg3,Arg4]),
 
1058
    {test,I,Lbl,[A2,A3,decode_field_flags(U),A4]};
 
1059
resolve_inst({bs_skip_utf16=I,[Lbl,Arg2,Arg3,{u,U}]},_,_,_) ->
 
1060
    [A2,A3] = resolve_args([Arg2,Arg3]),
 
1061
    {test,I,Lbl,[A2,A3,decode_field_flags(U)]};
 
1062
resolve_inst({bs_get_utf32=I,[Lbl,Arg2,Arg3,{u,U},Arg4]},_,_,_) ->
 
1063
    [A2,A3,A4] = resolve_args([Arg2,Arg3,Arg4]),
 
1064
    {test,I,Lbl,[A2,A3,decode_field_flags(U),A4]};
 
1065
resolve_inst({bs_skip_utf32=I,[Lbl,Arg2,Arg3,{u,U}]},_,_,_) ->
 
1066
    [A2,A3] = resolve_args([Arg2,Arg3]),
 
1067
    {test,I,Lbl,[A2,A3,decode_field_flags(U)]};
 
1068
resolve_inst({bs_utf8_size=I,[Lbl,Arg2,Arg3]},_,_,_) ->
 
1069
    [A2,A3] = resolve_args([Arg2,Arg3]),
 
1070
    {I,Lbl,A2,A3};
 
1071
resolve_inst({bs_put_utf8=I,[Lbl,{u,U},Arg3]},_,_,_) ->
 
1072
    [A3] = resolve_args([Arg3]),
 
1073
    {I,Lbl,decode_field_flags(U),A3};
 
1074
resolve_inst({bs_utf16_size=I,[Lbl,Arg2,Arg3]},_,_,_) ->
 
1075
    [A2,A3] = resolve_args([Arg2,Arg3]),
 
1076
    {I,Lbl,A2,A3};
 
1077
resolve_inst({bs_put_utf16=I,[Lbl,{u,U},Arg3]},_,_,_) ->
 
1078
    [A3] = resolve_args([Arg3]),
 
1079
    {I,Lbl,decode_field_flags(U),A3};
 
1080
resolve_inst({bs_put_utf32=I,[Lbl,{u,U},Arg3]},_,_,_) ->
 
1081
    [A3] = resolve_args([Arg3]),
 
1082
    {I,Lbl,decode_field_flags(U),A3};
 
1083
 
 
1084
%%
1048
1085
%% Catches instructions that are not yet handled.
1049
1086
%%
1050
1087
resolve_inst(X,_,_,_) -> ?exit({resolve_inst,X}).