File 2921-shell-read-records-from-module-in-escript-archive.patch of Package erlang

From 955fb439570b5e7ad7c0dcb01789d36abbc4e845 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?P=C3=A9ter=20G=C3=B6m=C3=B6ri?= <gomoripeti@gmail.com>
Date: Mon, 25 Jan 2021 13:35:26 +0100
Subject: [PATCH] shell: read records from module in escript/archive

Previously the `rr/1` shell function failed with the below error when
called for a module which was loaded from an archive or escript archive,
because beam_lib:chunks uses regular `file:open/2` to read from the
file. Now `erl_prim_loader:get_file/1` is used which supports file paths
in archives.

```
{error, beam_lib, {file_error,"<path_to_archive>/test_app.ez/test_app/ebin/test.beam", enotdir}}
```
---
 lib/stdlib/src/shell.erl        | 61 +++++++++++++++++++++------------
 lib/stdlib/test/shell_SUITE.erl | 35 ++++++++++++++++---
 2 files changed, 70 insertions(+), 26 deletions(-)

diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl
index 041a89f909..b397b2fc36 100644
--- a/lib/stdlib/src/shell.erl
+++ b/lib/stdlib/src/shell.erl
@@ -1186,6 +1186,8 @@ record_bindings(Recs0, Bs0) ->
 read_records(FileOrModule, Opts0) ->
     Opts = lists:delete(report_warnings, Opts0),
     case find_file(FileOrModule) of
+        {beam, Beam, File} ->
+            read_records_from_beam(Beam, File);
         {files,[File]} ->
             read_file_records(File, Opts);
         {files,Files} ->
@@ -1204,10 +1206,22 @@ read_records(FileOrModule, Opts0) ->
 find_file(Mod) when is_atom(Mod) ->
     case code:which(Mod) of
 	File when is_list(File) ->
-	    {files,[File]};
-	preloaded ->
-	    {_M,_Bin,File} = code:get_object_code(Mod),
-            {files,[File]};
+            %% Special cases:
+            %% - Modules not in the code path (loaded with code:load_abs/1):
+            %%   code:get_object_code/1 only searches in the code path
+            %%   but code:which/1 finds all loaded modules
+            %% - File can also be a file in an archive,
+            %%   beam_lib:chunks/2 cannot handle such paths but
+            %%   erl_prim_loader:get_file/1 can
+            case erl_prim_loader:get_file(File) of
+                {ok, Beam, _} ->
+                    {beam, Beam, File};
+                error ->
+                    {error, nofile}
+            end;
+    	preloaded ->
+	    {_M, Beam, File} = code:get_object_code(Mod),
+            {beam, Beam, File};
         _Else -> % non_existing, interpreted, cover_compiled
             {error,nofile}
     end;
@@ -1222,28 +1236,31 @@ find_file(File) ->
 read_file_records(File, Opts) ->
     case filename:extension(File) of
         ".beam" ->
-            case beam_lib:chunks(File, [abstract_code,"CInf"]) of
-                {ok,{_Mod,[{abstract_code,{Version,Forms}},{"CInf",CB}]}} ->
-                    case record_attrs(Forms) of
-                        [] when Version =:= raw_abstract_v1 ->
-                            [];
-                        [] -> 
-                            %% If the version is raw_X, then this test
-                            %% is unnecessary.
-                            try_source(File, CB);
-                        Records -> 
-                            Records
-                    end;
-                {ok,{_Mod,[{abstract_code,no_abstract_code},{"CInf",CB}]}} ->
-                    try_source(File, CB);
-                Error ->
-                    %% Could be that the "Abst" chunk is missing (pre R6).
-                    Error
-            end;
+            read_records_from_beam(File, File);
         _ ->
             parse_file(File, Opts)
     end.
 
+read_records_from_beam(Beam, File) ->
+    case beam_lib:chunks(Beam, [abstract_code,"CInf"]) of
+        {ok,{_Mod,[{abstract_code,{Version,Forms}},{"CInf",CB}]}} ->
+            case record_attrs(Forms) of
+                [] when Version =:= raw_abstract_v1 ->
+                    [];
+                [] ->
+                    %% If the version is raw_X, then this test
+                    %% is unnecessary.
+                    try_source(File, CB);
+                Records ->
+                    Records
+            end;
+        {ok,{_Mod,[{abstract_code,no_abstract_code},{"CInf",CB}]}} ->
+            try_source(File, CB);
+        Error ->
+            %% Could be that the "Abst" chunk is missing (pre R6).
+            Error
+    end.
+
 %% This is how the debugger searches for source files. See int.erl.
 try_source(Beam, CB) ->
     Os = case lists:keyfind(options, 1, binary_to_term(CB)) of
diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl
index 4d7a2ea078..4df0a2238a 100644
--- a/lib/stdlib/test/shell_SUITE.erl
+++ b/lib/stdlib/test/shell_SUITE.erl
@@ -64,8 +64,9 @@ end_per_testcase(_Case, Config) ->
     OrigPath = proplists:get_value(orig_path,Config),
     code:set_path(OrigPath),
     application:unset_env(stdlib, restricted_shell),
-    (catch code:purge(user_default)),
-    (catch code:delete(user_default)),
+    purge_and_delete(user_default),
+    %% used by `records' test case
+    purge_and_delete(test),
     ok.
 -endif.
 
@@ -298,8 +299,7 @@ restricted_local(Config) when is_list(Config) ->
 	comm_err(<<"begin shell:stop_restricted() end.">>),
     undefined =
 	application:get_env(stdlib, restricted_shell),
-    (catch code:purge(user_default)),
-    true = (catch code:delete(user_default)),
+    true = purge_and_delete(user_default),
     ok.
     
 
@@ -428,6 +428,30 @@ records(Config) when is_list(Config) ->
     [{error,invalid_filename}] = scan(<<"rr({foo}).">>),
     [[]] = scan(<<"rr(\"not_a_file\").">>),
 
+    %% load record from archive
+    true = purge_and_delete(test),
+
+    PrivDir = proplists:get_value(priv_dir, Config),
+    AppDir = filename:join(PrivDir, "test_app"),
+    ok = file:make_dir(AppDir),
+    AppEbinDir = filename:join(AppDir, "ebin"),
+    ok = file:make_dir(AppEbinDir),
+
+    ok = file:write_file(Test, Contents),
+    {ok, test} = compile:file(Test, [{outdir, AppEbinDir}]),
+
+    Ext = init:archive_extension(),
+    Archive = filename:join(PrivDir, "test_app" ++ Ext),
+    {ok, _} = zip:create(Archive, ["test_app"], [{compress, []}, {cwd, PrivDir}]),
+
+    ArchiveEbinDir = filename:join(Archive, "test_app/ebin"),
+    true = code:add_path(ArchiveEbinDir),
+    {module, test} = code:load_file(test),
+    BeamInArchive = filename:join(ArchiveEbinDir, "test.beam"),
+    BeamInArchive = code:which(test),
+
+    [[state]] = scan(<<"rr(test).">>),
+
     %% using records
     [2] = scan(<<"rd(foo,{bar}), record_info(size, foo).">>),
     [true] = scan(<<"rd(foo,{bar}), is_record(#foo{}, foo).">>),
@@ -3218,3 +3242,6 @@ start_node(Name, Xargs) ->
     global:sync(),
     N.
 
+purge_and_delete(Module) ->
+    (catch code:purge(Module)),
+    (catch code:delete(Module)).
-- 
2.26.2

openSUSE Build Service is sponsored by