File 3981-stdlib-fix-shell-save_module-1-so-that-it-saves-all-.patch of Package erlang

From c823722f7dc2cad5b5f1abf2eda9c7259e8d30e3 Mon Sep 17 00:00:00 2001
From: Fredrik Frantzen <frazze@erlang.org>
Date: Mon, 26 May 2025 12:27:11 +0200
Subject: [PATCH] stdlib: fix shell save_module/1 so that it saves all records
 in scope

---
 lib/stdlib/src/shell.erl        | 13 +++++++------
 lib/stdlib/test/shell_SUITE.erl | 14 +++++++++-----
 2 files changed, 16 insertions(+), 11 deletions(-)

diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl
index 8075e658cd..0a020e224e 100644
--- a/lib/stdlib/src/shell.erl
+++ b/lib/stdlib/src/shell.erl
@@ -1224,7 +1224,7 @@ local_func(lr, [], Bs, _Shell, _RT, FT, _Lf, _Ef) ->
 %% In theory, you may want to be able to load a module in to local table
 %% edit them, and then save it back to the file system.
 %% You may also want to be able to save a test module.
-local_func(save_module, [{string,_,PathToFile}], Bs, _Shell, _RT, FT, _Lf, _Ef) ->
+local_func(save_module, [{string,_,PathToFile}], Bs, _Shell, RT, FT, _Lf, _Ef) ->
     [_Path, FileName] = string:split("/"++PathToFile, "/", trailing),
     [Module, _] = string:split(FileName, ".", leading),
     Module1 = io_lib:fwrite("~tw",[list_to_atom(Module)]),
@@ -1232,8 +1232,8 @@ local_func(save_module, [{string,_,PathToFile}], Bs, _Shell, _RT, FT, _Lf, _Ef)
     Output = (
         "-module("++Module1++").\n\n" ++
         "-export(["++lists:join(",",Exports)++"]).\n\n"++
-        local_types(FT) ++
-        local_records(FT) ++
+        local_types(FT) ++ "\n" ++
+        all_records(RT) ++
         local_functions(FT)
     ),
     Ret = case filelib:is_file(PathToFile) of
@@ -1452,12 +1452,13 @@ local_functions(Keys, FT) ->
         end || {F, A} <- Keys]).
 %% Output local types
 local_types(FT) ->
-    lists:join($\n,
+    lists:join("\n\n",
         [TypeDef||{{type_def, _},TypeDef} <- ets:tab2list(FT)]).
 %% Output local records
 local_records(FT) ->
-    lists:join($\n,
-        [RecDef||{{record_def, _},RecDef} <- ets:tab2list(FT)]).
+        [list_to_binary(RecDef)||{{record_def, _},RecDef} <- ets:tab2list(FT)].
+all_records(RT) ->
+        [list_to_binary(erl_pp:attribute(RecDef) ++ "\n")||{ _,RecDef} <- ets:tab2list(RT)].
 write_and_compile_module(PathToFile, Output) ->
     case file:write_file(PathToFile, unicode:characters_to_binary(Output)) of
         ok -> c:c(PathToFile);
diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl
index 9b50f8cee3..22835896a8 100644
--- a/lib/stdlib/test/shell_SUITE.erl
+++ b/lib/stdlib/test/shell_SUITE.erl
@@ -689,12 +689,14 @@ local_definitions_save_to_module_and_forget(Config) when is_list(Config) ->
       <<"-spec my_func(X) -> X.\n"
         "my_func(X) -> X.\n"
         "lf().">>),
+    file:write_file("MY_MODULE_RECORD.hrl", "-record(grej,{b})."),
     %% Save local definitions to a module
     U = unicode:characters_to_binary("😊"),
-    "ok.\nok.\nok.\nok.\nok.\nok.\n{ok,'MY_MODULE'}.\n" = t({
+    "ok.\nok.\n[grej].\nok.\nok.\nok.\nok.\n{ok,'MY_MODULE'}.\n" = t({
       <<"-type hej() :: integer().\n"
         "-record(svej, {a :: hej()}).\n"
-        "my_func(#svej{a=A}) -> A.\n"
+        "rr(\"MY_MODULE_RECORD.hrl\").\n"
+        "my_func(#svej{a=A}) -> #grej{b=A}.\n"
         "-spec not_implemented(X) -> X.\n"
         "-spec 'my_func",U/binary,"'(X) -> X.\n"
         "'my_func",U/binary,"'(#svej{a=A}) -> A.\n"
@@ -702,14 +704,16 @@ local_definitions_save_to_module_and_forget(Config) when is_list(Config) ->
     %% Read back the newly created module
     {ok,<<"-module('MY_MODULE').\n\n"
           "-export([my_func/1,'my_func",240,159,152,138,"'/1]).\n\n"
-          "-type hej() :: integer().\n"
-          "-record(svej,{a :: hej()}).\n"
+          "-type hej() :: integer().\n\n"
+          "-record(grej,{b}).\n\n"
+          "-record(svej,{a :: hej()}).\n\n"
           "my_func(#svej{a = A}) ->\n"
-          "    A.\n\n"
+          "    #grej{b = A}.\n\n"
           "-spec 'my_func",240,159,152,138,"'(X) -> X.\n"
           "'my_func",240,159,152,138,"'(#svej{a = A}) ->\n"
           "    A.\n">>} = file:read_file("MY_MODULE.erl"),
     file:delete("MY_MODULE.erl"),
+    file:delete("MY_MODULE_RECORD.erl"),
 
     %% Forget one locally defined type
     "ok.\nok.\nok.\n-type svej() :: integer().\n.\nok.\n" = t(
-- 
2.43.0

openSUSE Build Service is sponsored by