File 4161-beam_lib-cover-Don-t-crash-when-an-abstract-code-bac.patch of Package erlang

From fba5a42890990a01aca764750ebb6a4913cbc24c Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Thu, 11 Feb 2021 15:26:25 +0100
Subject: [PATCH] beam_lib, cover: Don't crash when an abstract code backend is
 missing

On a computer without Elixir installed, `beam_lib` would crash when
asked to retrieve the abstract code for a BEAM file produced by the
Elixir compiler. Instead of crashing when the backend module is
missing, return `{error,{missing_backend,BeamFile,Backend}}`.
Also update `cover` to handle the new error from `beam_lib`.

Resolves #4353
---
 lib/stdlib/src/beam_lib.erl        | 11 +++++++++--
 lib/stdlib/test/beam_lib_SUITE.erl | 28 +++++++++++++++++++++++++--
 lib/tools/doc/src/cover.xml        |  3 ++-
 lib/tools/src/cover.erl            | 22 +++++++++++----------
 lib/tools/test/cover_SUITE.erl     | 31 ++++++++++++++++++++++++++++++
 5 files changed, 80 insertions(+), 15 deletions(-)

diff --git a/lib/stdlib/src/beam_lib.erl b/lib/stdlib/src/beam_lib.erl
index 0a6dc74bd0..23413f43b1 100644
--- a/lib/stdlib/src/beam_lib.erl
+++ b/lib/stdlib/src/beam_lib.erl
@@ -107,6 +107,7 @@
 -type chnk_rsn()  :: {'unknown_chunk', file:filename(), atom()}
                    | {'key_missing_or_invalid', file:filename(),
 		      'abstract_code' | 'debug_info'}
+                   | {'missing_backend', file:filename(), module()}
                    | info_rsn().
 -type cmp_rsn()   :: {'modules_different', module(), module()}
                    | {'chunks_different', chunkid()}
@@ -310,6 +311,9 @@ format_error(badfun) ->
     "not a fun or the fun has the wrong arity";
 format_error(exists) ->
     "a fun has already been installed";
+format_error({missing_backend, File, Backend}) ->
+    io_lib:format("~tp: Cannot retrieve abstract code because the backend ~p is missing",
+		  [File, Backend]);
 format_error(E) ->
     io_lib:format("~tp~n", [E]).
 
@@ -682,10 +686,13 @@ chunks_to_data([{abst_chunk, Name} | CNs], Chunks, File, Cs, Module, Atoms, L) -
     {NewAtoms, Ret} =
 	case catch chunk_to_data(debug_info, DbgiChunk, File, Cs, Atoms, Module) of
 	    {DbgiAtoms, {debug_info, {debug_info_v1, Backend, Metadata}}} ->
-		case Backend:debug_info(erlang_v1, Module, Metadata, []) of
+		try Backend:debug_info(erlang_v1, Module, Metadata, []) of
 		    {ok, Code} -> {DbgiAtoms, {abstract_code, {raw_abstract_v1, Code}}};
 		    {error, _} -> {DbgiAtoms, {abstract_code, no_abstract_code}}
-		end;
+                catch
+                    error:undef ->
+                        error({missing_backend,File,Backend})
+                end;
             {error,beam_lib,{key_missing_or_invalid,Path,debug_info}} ->
                 error({key_missing_or_invalid,Path,abstract_code});
 	    _ ->
diff --git a/lib/stdlib/test/beam_lib_SUITE.erl b/lib/stdlib/test/beam_lib_SUITE.erl
index 9ef85a15e0..e28301ec9e 100644
--- a/lib/stdlib/test/beam_lib_SUITE.erl
+++ b/lib/stdlib/test/beam_lib_SUITE.erl
@@ -36,7 +36,8 @@
 -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 	 init_per_group/2,end_per_group/2, 
 	 normal/1, error/1, cmp/1, cmp_literals/1, strip/1, strip_add_chunks/1, otp_6711/1,
-         building/1, md5/1, encrypted_abstr/1, encrypted_abstr_file/1]).
+         building/1, md5/1, encrypted_abstr/1, encrypted_abstr_file/1,
+         missing_debug_info_backend/1]).
 -export([test_makedep_abstract_code/1]).
 
 -export([init_per_testcase/2, end_per_testcase/2]).
@@ -48,7 +49,7 @@ suite() ->
 all() -> 
     [error, normal, cmp, cmp_literals, strip, strip_add_chunks, otp_6711,
      building, md5, encrypted_abstr, encrypted_abstr_file,
-     test_makedep_abstract_code
+     missing_debug_info_backend, test_makedep_abstract_code
     ].
 
 groups() -> 
@@ -816,6 +817,29 @@ write_crypt_file(Contents0) ->
     io:format("~s\n", [binary_to_list(Contents)]),
     ok = file:write_file(".erlang.crypt", Contents).
 
+%% GH-4353: Don't crash when the backend for generating the abstract code
+%% is missing.
+missing_debug_info_backend(Conf) ->
+    PrivDir = ?privdir,
+    Simple = filename:join(PrivDir, "simple"),
+    Source = Simple ++ ".erl",
+    BeamFile = Simple ++ ".beam",
+    simple_file(Source),
+
+    %% Create a debug_info chunk with a non-existing backend.
+    {ok,simple} = compile:file(Source, [{outdir,PrivDir}]),
+    {ok,simple,All0} = beam_lib:all_chunks(BeamFile),
+    FakeBackend = definitely__not__an__existing__backend,
+    FakeDebugInfo = {debug_info_v1, FakeBackend, nothing_here},
+    All = lists:keyreplace("Dbgi", 1, All0, {"Dbgi", term_to_binary(FakeDebugInfo)}),
+    {ok,NewBeam} = beam_lib:build_module(All),
+    ok = file:write_file(BeamFile, NewBeam),
+
+    %% beam_lib should not crash, but return an error.
+    verify(missing_backend, beam_lib:chunks(BeamFile, [abstract_code])),
+
+    ok.
+
 compare_chunks(File1, File2, ChunkIds) ->
     {ok, {_, Chunks1}} = beam_lib:chunks(File1, ChunkIds),
     {ok, {_, Chunks2}} = beam_lib:chunks(File2, ChunkIds),
diff --git a/lib/tools/doc/src/cover.xml b/lib/tools/doc/src/cover.xml
index 8073bfc528..0889a16f65 100644
--- a/lib/tools/doc/src/cover.xml
+++ b/lib/tools/doc/src/cover.xml
@@ -217,9 +217,10 @@
 	<v>ModFiles = ModFile | [ModFile]</v>
         <v>ModFile = Module | BeamFile</v>
         <v>&nbsp;Module = atom()</v>
+        <v>&nbsp;BackendModule = atom()</v>
         <v>&nbsp;BeamFile = string()</v>
         <v>Result = {ok,Module} | {error,BeamFile} | {error,Reason}</v>
-        <v>&nbsp;Reason = non_existing | {no_abstract_code,BeamFile} | {encrypted_abstract_code,BeamFile} | {already_cover_compiled,no_beam_found,Module} | not_main_node</v>
+        <v>&nbsp;Reason = non_existing | {no_abstract_code,BeamFile} | {{missing_backend,BackendModule},BeamFile} | {encrypted_abstract_code,BeamFile} | {already_cover_compiled,no_beam_found,Module} | not_main_node</v>
       </type>
       <desc>
         <p>Does the same as <c>compile/1,2</c>, but uses an existing
diff --git a/lib/tools/src/cover.erl b/lib/tools/src/cover.erl
index 9f86a68942..d1781c7b08 100644
--- a/lib/tools/src/cover.erl
+++ b/lib/tools/src/cover.erl
@@ -1552,14 +1552,12 @@ do_compile2(File, UserOptions, LocalOnly) ->
 do_compile_beam1(Module,Beam,UserOptions,LocalOnly) ->
     %% Clear database
     do_clear(Module),
-    
+
     %% Extract the abstract format.
     case get_abstract_code(Module, Beam) of
-	no_abstract_code=E ->
-	    {error,E};
-	encrypted_abstract_code=E ->
-	    {error,E};
-	{raw_abstract_v1,Code} ->
+	{error,_}=Error ->
+            Error;
+	{ok,{raw_abstract_v1,Code}} ->
             Forms0 = epp:interpret_file_attribute(Code),
 	    case find_main_filename(Forms0) of
 		{ok,MainFile} ->
@@ -1568,7 +1566,7 @@ do_compile_beam1(Module,Beam,UserOptions,LocalOnly) ->
 		Error ->
 		    Error
 	    end;
-	{_VSN,_Code} ->
+	{ok,{_VSN,_Code}} ->
 	    %% Wrong version of abstract code. Just report that there
 	    %% is no abstract code.
 	    {error,no_abstract_code}
@@ -1577,10 +1575,14 @@ do_compile_beam1(Module,Beam,UserOptions,LocalOnly) ->
 get_abstract_code(Module, Beam) ->
     case beam_lib:chunks(Beam, [abstract_code]) of
 	{ok, {Module, [{abstract_code, AbstractCode}]}} ->
-	    AbstractCode;
+            case AbstractCode of
+                no_abstract_code=E -> {error, E};
+                _ -> {ok,AbstractCode}
+            end;
 	{error,beam_lib,{key_missing_or_invalid,_,_}} ->
-	    encrypted_abstract_code;
-	Error -> Error
+	    {error,encrypted_abstract_code};
+	{error,beam_lib,{missing_backend,_,Backend}} ->
+	    {error,{missing_backend,Backend}}
     end.
 
 do_compile_beam2(Module,Beam,UserOptions,Forms0,MainFile,LocalOnly) ->
diff --git a/lib/tools/test/cover_SUITE.erl b/lib/tools/test/cover_SUITE.erl
index f4c3a0e3b6..c12ea581e2 100644
--- a/lib/tools/test/cover_SUITE.erl
+++ b/lib/tools/test/cover_SUITE.erl
@@ -31,6 +31,7 @@ all() ->
     NoStartStop = [eif,otp_5305,otp_5418,otp_7095,otp_8273,
                    otp_8340,otp_8188,compile_beam_opts,eep37,
                    analyse_no_beam, line_0, compile_beam_no_file,
+                   compile_beam_missing_backend,
                    otp_13277, otp_13289, gh_4796],
     StartStop = [start, compile, analyse, misc, stop,
                  distribution, reconnect, die_and_reconnect,
@@ -1706,12 +1707,42 @@ compile_beam_no_file(Config) ->
     [{error,{no_file_attribute,BeamFile}}] = cover:compile_beam_directory(Dir),
     ok.
 
+%% GH-4353: Don't crash when the backend for generating the abstract code
+%% is missing.
+compile_beam_missing_backend(Config) ->
+    PrivDir = proplists:get_value(priv_dir, Config),
+    Dir = filename:join(PrivDir, ?FUNCTION_NAME),
+    ok = filelib:ensure_dir(filename:join(Dir, "*")),
+    code:add_patha(Dir),
+    Str = lists:append(
+            ["-module(no_backend).\n"
+             "-compile(export_all).\n"
+             "foo() -> ok.\n"]),
+    TT = do_scan(Str),
+    Forms = [ begin {ok,Y} = erl_parse:parse_form(X),Y end || X <- TT ],
+    {ok,_,Bin} = compile:forms(Forms, [debug_info]),
+
+    %% Create a debug_info chunk with a non-existing backend.
+    {ok,no_backend,All0} = beam_lib:all_chunks(Bin),
+    FakeBackend = definitely__not__an__existing__backend,
+    FakeDebugInfo = {debug_info_v1,FakeBackend,nothing_here},
+    All = lists:keyreplace("Dbgi", 1, All0, {"Dbgi", term_to_binary(FakeDebugInfo)}),
+    {ok,NewBeam} = beam_lib:build_module(All),
+    BeamFile = filename:join(Dir, "no_backend.beam"),
+    ok = file:write_file(BeamFile, NewBeam),
+
+    {error,{{missing_backend,FakeBackend},BeamFile}} = cover:compile_beam(no_backend),
+    [{error,{{missing_backend,FakeBackend},BeamFile}}] = cover:compile_beam_directory(Dir),
+
+    ok.
+
 do_scan([]) ->
     [];
 do_scan(Str) ->
     {done,{ok,T,_},C} = erl_scan:tokens([],Str,0),
     [ T | do_scan(C) ].
 
+
 %% PR 856. Fix a bc bug.
 otp_13277(Config) ->
     Test = <<"-module(t).
-- 
2.26.2

openSUSE Build Service is sponsored by