File 2853-stdlib-Make-shell-expand-work-with-all-available-mod.patch of Package erlang

From 9fc49083063112abdf18775c41460f9b4ea0697e Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Wed, 29 Jan 2020 15:51:47 +0100
Subject: [PATCH 03/27] stdlib: Make shell expand work with all available
 modules

Before this change all modules had to be loaded for the autocompletion
to work, now they only have to be in the path.

This also changes so that if you hit <TAB> when there is nothing
to complete only a bell is signaled.
---
 lib/stdlib/src/edlin_expand.erl                    | 40 ++++++++++++++--------
 lib/stdlib/test/Makefile                           |  5 ---
 lib/stdlib/test/edlin_expand_SUITE.erl             | 32 +++++++++++------
 .../ExpandTestCaps.erl                             |  0
 .../ExpandTestCaps1.erl                            |  0
 .../{ => edlin_expand_SUITE_data}/expand_test.erl  |  0
 .../{ => edlin_expand_SUITE_data}/expand_test1.erl |  0
 .../unicode_expand.erl                             |  0
 8 files changed, 46 insertions(+), 31 deletions(-)
 rename lib/stdlib/test/{ => edlin_expand_SUITE_data}/ExpandTestCaps.erl (100%)
 rename lib/stdlib/test/{ => edlin_expand_SUITE_data}/ExpandTestCaps1.erl (100%)
 rename lib/stdlib/test/{ => edlin_expand_SUITE_data}/expand_test.erl (100%)
 rename lib/stdlib/test/{ => edlin_expand_SUITE_data}/expand_test1.erl (100%)
 rename lib/stdlib/test/{ => edlin_expand_SUITE_data}/unicode_expand.erl (100%)

diff --git a/lib/stdlib/src/edlin_expand.erl b/lib/stdlib/src/edlin_expand.erl
index bdcefda6e5..da6671b013 100644
--- a/lib/stdlib/src/edlin_expand.erl
+++ b/lib/stdlib/src/edlin_expand.erl
@@ -43,24 +43,32 @@ expand(Bef0) ->
  	    expand_module_name(Word)
     end.
 
+expand_module_name("") ->
+    {no, [], []};
 expand_module_name(Prefix) ->
-    match(Prefix, code:all_loaded(), ":").
+    match(Prefix, [{list_to_atom(M),P} || {M,P,_} <- code:all_available()], ":").
 
 expand_function_name(ModStr, FuncPrefix) ->
     case to_atom(ModStr) of
 	{ok, Mod} ->
-	    case erlang:module_loaded(Mod) of
-		true ->
-		    L = Mod:module_info(),
-		    case lists:keyfind(exports, 1, L) of
-			{_, Exports} ->
-			    match(FuncPrefix, Exports, "(");
-			_ ->
-			    {no, [], []}
-		    end;
-		false ->
-		    {no, [], []}
-	    end;
+            Exports =
+                case erlang:module_loaded(Mod) of
+                    true ->
+                        Mod:module_info(exports);
+                    false ->
+                        case beam_lib:chunks(code:which(Mod), [exports]) of
+                            {ok, {Mod, [{exports,E}]}} ->
+                                E;
+                            _ ->
+                                {no, [], []}
+                        end
+                end,
+            case Exports of
+                {no, [], []} ->
+                    {no, [], []};
+                Exports ->
+                    match(FuncPrefix, Exports, "(")
+            end;
 	error ->
 	    {no, [], []}
     end.
@@ -99,8 +107,10 @@ match(Prefix, Alts, Extra0) ->
  	    {no, [], []}
     end.
 
-flat_write(T) ->
-    lists:flatten(io_lib:fwrite("~tw",[T])).
+flat_write(T) when is_atom(T) ->
+    lists:flatten(io_lib:fwrite("~tw",[T]));
+flat_write(S) ->
+    S.
 
 %% Return the list of names L in multiple columns.
 format_matches(L) ->
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile
index 7f7a0834ba..d6717ccaa6 100644
--- a/lib/stdlib/test/Makefile
+++ b/lib/stdlib/test/Makefile
@@ -34,11 +34,6 @@ MODULES= \
 	escript_SUITE \
 	ets_SUITE \
 	ets_tough_SUITE \
-	expand_test \
-	expand_test1 \
-	unicode_expand \
-	ExpandTestCaps \
-	ExpandTestCaps1 \
 	filelib_SUITE \
 	file_sorter_SUITE \
 	filename_SUITE \
diff --git a/lib/stdlib/test/edlin_expand_SUITE.erl b/lib/stdlib/test/edlin_expand_SUITE.erl
index 5c2b1965ba..dd6b25a531 100644
--- a/lib/stdlib/test/edlin_expand_SUITE.erl
+++ b/lib/stdlib/test/edlin_expand_SUITE.erl
@@ -27,6 +27,7 @@
 -include_lib("common_test/include/ct.hrl").
 
 init_per_testcase(_Case, Config) ->
+    cleanup(),
     Config.
 
 end_per_testcase(_Case, _Config) ->
@@ -44,10 +45,6 @@ groups() ->
     [].
 
 init_per_suite(Config) ->
-    (catch code:delete(expand_test)),
-    (catch code:delete(expand_test1)),
-    (catch code:delete('ExpandTestCaps')),
-    (catch code:delete('ExpandTestCaps1')),
     Config.
 
 end_per_suite(_Config) ->
@@ -59,9 +56,15 @@ init_per_group(_GroupName, Config) ->
 end_per_group(_GroupName, Config) ->
     Config.
 
+cleanup() ->
+    [try
+         code:purge(M),
+         code:delete(M)
+     catch _:_ -> ok end || M <- [expand_test, expand_test1,
+                                  'ExpandTestCaps', 'ExpandTestCaps2']].
 
 normal(Config) when is_list(Config) ->
-    {module,expand_test} = c:l(expand_test),
+    {module,expand_test} = compile_and_load(Config,expand_test),
     %% These tests might fail if another module with the prefix
     %% "expand_" happens to also be loaded.
     {yes, "test:", []} = do_expand("expand_"),
@@ -80,8 +83,8 @@ normal(Config) when is_list(Config) ->
 
 %% Normal module name, some function names using quoted atoms.
 quoted_fun(Config) when is_list(Config) ->
-    {module,expand_test} = c:l(expand_test),
-    {module,expand_test1} = c:l(expand_test1),
+    {module,expand_test} = compile_and_load(Config,expand_test),
+    {module,expand_test1} = compile_and_load(Config,expand_test1),
     %% should be no colon after test this time
     {yes, "test", []} = do_expand("expand_"),
     {no, [], []} = do_expand("expandXX_"),
@@ -112,7 +115,7 @@ quoted_fun(Config) when is_list(Config) ->
     ok.
 
 quoted_module(Config) when is_list(Config) ->
-    {module,'ExpandTestCaps'} = c:l('ExpandTestCaps'),
+    {module,'ExpandTestCaps'} = compile_and_load(Config,'ExpandTestCaps'),
     {yes, "Caps':", []} = do_expand("'ExpandTest"),
     {no,[],
      [{"a_fun_name",1},
@@ -125,8 +128,8 @@ quoted_module(Config) when is_list(Config) ->
     ok.
 
 quoted_both(Config) when is_list(Config) ->
-    {module,'ExpandTestCaps'} = c:l('ExpandTestCaps'),
-    {module,'ExpandTestCaps1'} = c:l('ExpandTestCaps1'),
+    {module,'ExpandTestCaps'} = compile_and_load(Config,'ExpandTestCaps'),
+    {module,'ExpandTestCaps1'} = compile_and_load(Config,'ExpandTestCaps1'),
     %% should be no colon (or quote) after test this time
     {yes, "Caps", []} = do_expand("'ExpandTest"),
     {no,[],[{"'#weird-fun-name'",0},
@@ -229,7 +232,7 @@ check_trailing([I|Str], ArityStr, Suffix, Dots) ->
     end.
 
 unicode(Config) when is_list(Config) ->
-    {module,unicode_expand} = c:l('unicode_expand'),
+    {module,unicode_expand} = compile_and_load(Config,'unicode_expand'),
     {no,[],[{"'кlирилли́ческий атом'",0},
             {"'кlирилли́ческий атом'",1},
             {"'кlирилли́ческий атомB'",1},
@@ -253,3 +256,10 @@ do_expand(String) ->
 
 do_format(StringList) ->
     lists:flatten(edlin_expand:format_matches(StringList)).
+
+compile_and_load(Config,Module) ->
+    Filename = filename:join(
+                 proplists:get_value(data_dir,Config),
+                 atom_to_list(Module)),
+    {ok,Module,Bin} = compile:file(Filename, [binary]),
+    code:load_binary(Module, Filename, Bin).
diff --git a/lib/stdlib/test/ExpandTestCaps.erl b/lib/stdlib/test/edlin_expand_SUITE_data/ExpandTestCaps.erl
similarity index 100%
rename from lib/stdlib/test/ExpandTestCaps.erl
rename to lib/stdlib/test/edlin_expand_SUITE_data/ExpandTestCaps.erl
diff --git a/lib/stdlib/test/ExpandTestCaps1.erl b/lib/stdlib/test/edlin_expand_SUITE_data/ExpandTestCaps1.erl
similarity index 100%
rename from lib/stdlib/test/ExpandTestCaps1.erl
rename to lib/stdlib/test/edlin_expand_SUITE_data/ExpandTestCaps1.erl
diff --git a/lib/stdlib/test/expand_test.erl b/lib/stdlib/test/edlin_expand_SUITE_data/expand_test.erl
similarity index 100%
rename from lib/stdlib/test/expand_test.erl
rename to lib/stdlib/test/edlin_expand_SUITE_data/expand_test.erl
diff --git a/lib/stdlib/test/expand_test1.erl b/lib/stdlib/test/edlin_expand_SUITE_data/expand_test1.erl
similarity index 100%
rename from lib/stdlib/test/expand_test1.erl
rename to lib/stdlib/test/edlin_expand_SUITE_data/expand_test1.erl
diff --git a/lib/stdlib/test/unicode_expand.erl b/lib/stdlib/test/edlin_expand_SUITE_data/unicode_expand.erl
similarity index 100%
rename from lib/stdlib/test/unicode_expand.erl
rename to lib/stdlib/test/edlin_expand_SUITE_data/unicode_expand.erl
-- 
2.16.4

openSUSE Build Service is sponsored by