1%% ``Licensed under the Apache License, Version 2.0 (the "License");
2%% you may not use this file except in compliance with the License.
3%% You may obtain a copy of the License at
4%%
5%%     http://www.apache.org/licenses/LICENSE-2.0
6%%
7%% Unless required by applicable law or agreed to in writing, software
8%% distributed under the License is distributed on an "AS IS" BASIS,
9%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
10%% See the License for the specific language governing permissions and
11%% limitations under the License.
12%%
13%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
14%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
15%% AB. All Rights Reserved.''
16%%
17%%     $Id: beam_listing.erl,v 1.1 2008/12/17 09:53:41 mikpe Exp $
18%%
19-module(beam_listing).
20
21-export([module/2]).
22
23-include("v3_life.hrl").
24
25-import(lists, [foreach/2]).
26
27module(File, Core) when element(1, Core) == c_module ->
28    %% This is a core module.
29    io:put_chars(File, core_pp:format(Core));
30module(File, Kern) when element(1, Kern) == k_mdef ->
31    %% This is a kernel module.
32    io:put_chars(File, v3_kernel_pp:format(Kern));
33    %%io:put_chars(File, io_lib:format("~p~n", [Kern]));
34module(File, {Mod,Exp,Attr,Kern}) ->
35    %% This is output from beam_life (v3).
36    io:fwrite(File, "~w.~n~p.~n~p.~n", [Mod,Exp,Attr]),
37    foreach(fun (F) -> function(File, F) end, Kern);
38module(Stream, {Mod,Exp,Attr,Code,NumLabels}) ->
39    %% This is output from beam_codegen.
40    io:format(Stream, "{module, ~s}.  %% version = ~w\n",
41	      [Mod, beam_opcodes:format_number()]),
42    io:format(Stream, "\n{exports, ~p}.\n", [Exp]),
43    io:format(Stream, "\n{attributes, ~p}.\n", [Attr]),
44    io:format(Stream, "\n{labels, ~p}.\n", [NumLabels]),
45    foreach(
46      fun ({function,Name,Arity,Entry,Asm}) ->
47	      io:format(Stream, "\n\n{function, ~w, ~w, ~w}.\n",
48			[Name, Arity, Entry]),
49	      foreach(fun(Op) -> print_op(Stream, Op) end, Asm) end,
50      Code);
51module(Stream, {Mod,Exp,Inter}) ->
52    %% Other kinds of intermediate formats.
53    io:fwrite(Stream, "~w.~n~p.~n", [Mod,Exp]),
54    foreach(fun (F) -> io:format(Stream, "~p.\n", [F]) end, Inter);
55module(Stream, [_|_]=Fs) ->
56    %% Form-based abstract format.
57    foreach(fun (F) -> io:format(Stream, "~p.\n", [F]) end, Fs).
58
59print_op(Stream, Label) when element(1, Label) == label ->
60    io:format(Stream, "  ~p.\n", [Label]);
61print_op(Stream, Op) ->
62    io:format(Stream, "    ~p.\n", [Op]).
63
64function(File, {function,Name,Arity,Args,Body,Vdb}) ->
65    io:nl(File),
66    io:format(File, "function ~p/~p.\n", [Name,Arity]),
67    io:format(File, " ~p.\n", [Args]),
68    print_vdb(File, Vdb),
69    put(beam_listing_nl, true),
70    foreach(fun(F) -> format(File, F, []) end, Body),
71    nl(File),
72    erase(beam_listing_nl).
73
74format(File, #l{ke=Ke,i=I,vdb=Vdb}, Ind) ->
75    nl(File),
76    ind_format(File, Ind, "~p ", [I]),
77    print_vdb(File, Vdb),
78    nl(File),
79    format(File, Ke, Ind);
80format(File, Tuple, Ind) when is_tuple(Tuple) ->
81    ind_format(File, Ind, "{", []),
82    format_list(File, tuple_to_list(Tuple), [$\s|Ind]),
83    ind_format(File, Ind, "}", []);
84format(File, List, Ind) when is_list(List) ->
85    ind_format(File, Ind, "[", []),
86    format_list(File, List, [$\s|Ind]),
87    ind_format(File, Ind, "]", []);
88format(File, F, Ind) ->
89    ind_format(File, Ind, "~p", [F]).
90
91format_list(File, [F], Ind) ->
92    format(File, F, Ind);
93format_list(File, [F|Fs], Ind) ->
94    format(File, F, Ind),
95    ind_format(File, Ind, ",", []),
96    format_list(File, Fs, Ind);
97format_list(_, [], _) -> ok.
98
99
100print_vdb(File, [{Var,F,E}|Vs]) ->
101    io:format(File, "~p:~p..~p ", [Var,F,E]),
102    print_vdb(File, Vs);
103print_vdb(_, []) -> ok.
104
105ind_format(File, Ind, Format, Args) ->
106    case get(beam_listing_nl) of
107	true ->
108	    put(beam_listing_nl, false),
109	    io:put_chars(File, Ind);
110	false -> ok
111    end,
112    io:format(File, Format, Args).
113
114nl(File) ->
115    case put(beam_listing_nl, true) of
116	true -> ok;
117	false -> io:nl(File)
118    end.
119