File 2361-compiler-Comment-BEAM-assembly-with-callee-names-in-.patch of Package erlang

From 841db7654f66f0f2c696b7f601ddc3b91d8e7db5 Mon Sep 17 00:00:00 2001
From: Frej Drejhammar <frej.drejhammar@gmail.com>
Date: Wed, 30 Jun 2021 13:36:56 +0200
Subject: [PATCH] compiler: Comment BEAM assembly with callee names in
 clear-text

Looking at BEAM assembly listings, figuring out where a local call
goes requires you to keep track of which `{f,<index>}`-label
corresponds to which function. This patch increases the readability of
the assembly listing by annotating each call instruction with a
comment containing the name of the called function.

Instead of, for example, `{call,1,{f,4}}.`, the listing will now say
`{call,1,{f,4}}. % foo/1`.
---
 lib/compiler/src/beam_listing.erl             | 25 +++++++---
 lib/compiler/test/compile_SUITE.erl           | 24 +++++++++-
 .../test/compile_SUITE_data/asm_labels.erl    | 47 +++++++++++++++++++
 3 files changed, 87 insertions(+), 9 deletions(-)
 create mode 100644 lib/compiler/test/compile_SUITE_data/asm_labels.erl

diff --git a/lib/compiler/src/beam_listing.erl b/lib/compiler/src/beam_listing.erl
index 6121593b11..dc3044bec4 100644
--- a/lib/compiler/src/beam_listing.erl
+++ b/lib/compiler/src/beam_listing.erl
@@ -26,7 +26,7 @@
 -include("beam_ssa.hrl").
 -include("beam_disasm.hrl").
 
--import(lists, [foreach/2]).
+-import(lists, [foldl/3, foreach/2]).
 
 -type code() :: cerl:c_module()
               | beam_utils:module_code()
@@ -55,18 +55,29 @@ module(Stream, {Mod,Exp,Attr,Code,NumLabels}) ->
     io:format(Stream, "\n{exports, ~p}.\n", [Exp]),
     io:format(Stream, "\n{attributes, ~p}.\n", [Attr]),
     io:format(Stream, "\n{labels, ~p}.\n", [NumLabels]),
+    Lbl2Fun = foldl(fun({function,Name,Arity,Entry,_}, Map) ->
+                            Map#{ Entry => {Name,Arity} }
+                    end, #{}, Code),
     foreach(
       fun ({function,Name,Arity,Entry,Asm}) ->
 	      io:format(Stream, "\n\n{function, ~w, ~w, ~w}.\n",
 			[Name, Arity, Entry]),
-	      io:put_chars(Stream, format_asm(Asm))
+	      io:put_chars(Stream, format_asm(Asm, Lbl2Fun))
       end, Code);
 module(Stream, [_|_]=Fs) ->
     %% Form-based abstract format.
     foreach(fun (F) -> io:format(Stream, "~p.\n", [F]) end, Fs).
 
-format_asm([{label,L}|Is]) ->
-    [io_lib:format("  {label,~p}.\n", [L])|format_asm(Is)];
-format_asm([I|Is]) ->
-    [io_lib:format("    ~p", [I]),".\n"|format_asm(Is)];
-format_asm([]) -> [].
+format_asm([{label,L}|Is], Lbl2Fun) ->
+    [io_lib:format("  {label,~p}.\n", [L])|format_asm(Is, Lbl2Fun)];
+format_asm([I={Call,_,L}|Is], Lbl2Fun) when Call =:= call; Call =:= call_only ->
+    format_asm_call(L, I, Is, Lbl2Fun);
+format_asm([I={call_last,_,L,_}|Is], Lbl2Fun) ->
+    format_asm_call(L, I, Is, Lbl2Fun);
+format_asm([I|Is], Lbl2Fun) ->
+    [io_lib:format("    ~p", [I]),".\n"|format_asm(Is, Lbl2Fun)];
+format_asm([], _) -> [].
+
+format_asm_call({f,L}, I, Is, Lbl2Fun) ->
+    {N,A} = map_get(L, Lbl2Fun),
+    [io_lib:format("    ~p. % ~p/~p\n", [I, N, A])|format_asm(Is, Lbl2Fun)].
diff --git a/lib/compiler/test/compile_SUITE.erl b/lib/compiler/test/compile_SUITE.erl
index c9495c3755..5d75f0862a 100644
--- a/lib/compiler/test/compile_SUITE.erl
+++ b/lib/compiler/test/compile_SUITE.erl
@@ -33,7 +33,7 @@
 	 other_output/1, kernel_listing/1, encrypted_abstr/1,
 	 strict_record/1, utf8_atoms/1, utf8_functions/1, extra_chunks/1,
 	 cover/1, env/1, core_pp/1, tuple_calls/1,
-	 core_roundtrip/1, asm/1,
+	 core_roundtrip/1, asm/1, asm_labels/1,
 	 sys_pre_attributes/1, dialyzer/1, no_core_prepare/1,
 	 warnings/1, pre_load_check/1, env_compiler_options/1,
          bc_options/1, deterministic_include/1, deterministic_paths/1,
@@ -52,7 +52,7 @@ all() ->
      binary, makedep, cond_and_ifdef, listings, listings_big,
      other_output, kernel_listing, encrypted_abstr, tuple_calls,
      strict_record, utf8_atoms, utf8_functions, extra_chunks,
-     cover, env, core_pp, core_roundtrip, asm, no_core_prepare,
+     cover, env, core_pp, core_roundtrip, asm, asm_labels, no_core_prepare,
      sys_pre_attributes, dialyzer, warnings, pre_load_check,
      env_compiler_options, custom_debug_info, bc_options,
      custom_compile_info, deterministic_include, deterministic_paths,
@@ -1283,6 +1283,26 @@ do_asm(Beam, Outdir) ->
 	    error
     end.
 
+%% Compile a crafted file which produces the three call instructions
+%% which should have a comment with the called function in clear
+%% text. We check that the expected functions and comments occur in
+%% the listing.
+
+asm_labels(Config) ->
+    DataDir = proplists:get_value(data_dir, Config),
+    PrivDir = proplists:get_value(priv_dir, Config),
+    InFile = filename:join(DataDir, "asm_labels.erl"),
+    OutDir = filename:join(PrivDir, "asm_labels"),
+    OutFile = filename:join(OutDir, "asm_labels.S"),
+    ok = file:make_dir(OutDir),
+    {ok,asm_labels} = compile:file(InFile, ['S',{outdir,OutDir}]),
+    {ok,Listing} = file:read_file(OutFile),
+    Os = [global,multiline,{capture,all_but_first,list}],
+    {match,[_]} = re:run(Listing, "({call,.+,{f,.+}}\\. % foo/1)", Os),
+    {match,[_]} = re:run(Listing, "({call_only,.+,{f,.+}}\\. % foo/1)", Os),
+    {match,[_]} = re:run(Listing, "({call_last,.+,{f,.+},.+}\\. % bar/1)", Os),
+    ok = file:del_dir_r(OutDir).
+
 sys_pre_attributes(Config) ->
     DataDir = proplists:get_value(data_dir, Config),
     File = filename:join(DataDir, "attributes.erl"),
diff --git a/lib/compiler/test/compile_SUITE_data/asm_labels.erl b/lib/compiler/test/compile_SUITE_data/asm_labels.erl
new file mode 100644
index 0000000000..59571f5539
--- /dev/null
+++ b/lib/compiler/test/compile_SUITE_data/asm_labels.erl
@@ -0,0 +1,47 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2021. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+%% A module which when compiled to a BEAM assembly listing will
+%% contain call instructions with comments containing the called
+%% function in clear text.
+
+-module(asm_labels).
+
+-export([foo/0, bar/0]).
+
+%% Expected to generate a `call_only` instruction
+foo() ->
+    foo(10).
+
+%% Expected to generate a `call` instruction
+foo(0) ->
+    17;
+foo(N) ->
+    foo(N-1) + 1.
+
+%% Expected to generate a `call_last` instruction
+bar() ->
+    receive
+	X ->
+	    bar(X)
+    end.
+
+bar([]) ->
+    ok.
-- 
2.31.1

openSUSE Build Service is sponsored by