File 0229-stdlib-fix-completion-bug-when-a-reserved-word-is-fo.patch of Package erlang

From d9b5fe3ec80f9702b3a1f87b19533a729d0719af Mon Sep 17 00:00:00 2001
From: Fredrik Frantzen <frazze@erlang.org>
Date: Fri, 14 Mar 2025 06:40:32 +0100
Subject: [PATCH 2/2] stdlib: fix completion bug when a reserved word is
 followed by a '('

prevents a crashing the shell when completion is attempted on "case(".

OTP-19511
---
 lib/stdlib/src/edlin_expand.erl        | 32 +++++++++++++++-----------
 lib/stdlib/src/shell.erl               |  2 +-
 lib/stdlib/test/edlin_expand_SUITE.erl |  7 ++++--
 lib/stdlib/test/shell_SUITE.erl        |  4 ++--
 4 files changed, 26 insertions(+), 19 deletions(-)

diff --git a/lib/stdlib/src/edlin_expand.erl b/lib/stdlib/src/edlin_expand.erl
index 70c41fe8d2..30ec5e0e1b 100644
--- a/lib/stdlib/src/edlin_expand.erl
+++ b/lib/stdlib/src/edlin_expand.erl
@@ -393,8 +393,8 @@ is_type(Type, Cs, String) ->
     catch
         _:_ ->
             %% Types not possible to deduce with erl_parse
-            % If string contains variables, erl_parse:parse_term will fail, but we
-            % consider them valid sooo.. lets replace them with the atom var
+            %% If string contains variables, erl_parse:parse_term will fail, but we
+            %% consider them valid sooo.. lets replace them with the atom var
             B = [(fun({var, Anno, _}) -> {atom, Anno, var}; (Token) -> Token end)(X) || X <- A],
             try
                 {ok, Term2} = erl_parse:parse_term(B),
@@ -730,29 +730,33 @@ expand_filepath(PathPrefix, Word) ->
     end.
 
 shell(Fun) ->
-    {ok, [{atom, _, Fun1}], _} = erl_scan:string(Fun),
-    case shell:local_func(Fun1) of
+    case shell:local_func(Fun) of
         true -> "shell";
         false -> "user_defined"
     end.
 
 -doc false.
+shell_default_or_bif(Fun) when is_atom(Fun) ->
+    case lists:member(Fun, [E || {E,_} <- get_exports(shell_default)]) of
+        true -> "shell_default";
+        false -> bif(Fun)
+    end;
 shell_default_or_bif(Fun) ->
     case erl_scan:string(Fun) of
-        {ok, [{var, _, _}], _} -> [];
-        {ok, [{atom, _, Fun1}], _} ->
-            case lists:member(Fun1, [E || {E,_}<-get_exports(shell_default)]) of
-                true -> "shell_default";
-                _ -> bif(Fun)
-            end
+        {ok, [{atom, _, Fun1}], _} -> shell_default_or_bif(Fun1);
+        _ -> []
     end.
 
 -doc false.
-bif(Fun) ->
-    {ok, [{atom, _, Fun1}], _} = erl_scan:string(Fun),
-    case lists:member(Fun1, [E || {E,A}<-get_exports(erlang), erl_internal:bif(E,A)]) of
+bif(Fun) when is_atom(Fun) ->
+    case lists:member(Fun, [E || {E,_} <- get_exports(erlang)]) of
         true -> "erlang";
-        _ -> shell(Fun)
+        false -> shell(Fun)
+    end;
+bif(Fun) ->
+    case erl_scan:string(Fun) of
+        {ok, [{atom, _, Fun1}], _} -> bif(Fun1);
+        _ -> []
     end.
 
 expand_string(Bef0) ->
diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl
index ad0228f647..e3ec74a4b2 100644
--- a/lib/stdlib/src/shell.erl
+++ b/lib/stdlib/src/shell.erl
@@ -1176,7 +1176,7 @@ init_dict([]) -> true.
 %% non_builtin_local_func/3 (user_default/shell_default).
 %% fd, ft and td should not be exposed to the user
 -doc false.
-local_func() -> [v,h,b,f,ff,fl,lf,lr,lt,rd,rf,rl,rp,rr,tf,save_module,history,results,catch_exception].
+local_func() -> [v,h,b,f,fd,ff,fl,lf,lr,lt,rd,rf,rl,rp,rr,tf,save_module,history,results,catch_exception].
 -doc false.
 local_func(Func) ->
     lists:member(Func, local_func()).
diff --git a/lib/stdlib/test/edlin_expand_SUITE.erl b/lib/stdlib/test/edlin_expand_SUITE.erl
index 15abaaa7f0..f69bda342d 100644
--- a/lib/stdlib/test/edlin_expand_SUITE.erl
+++ b/lib/stdlib/test/edlin_expand_SUITE.erl
@@ -448,8 +448,11 @@ get_coverage(Config) ->
     do_expand("M#"),
     do_expand("#non_existant_record"),
     do_expand("#a_record{ non_existand_field"),
-    
-    
+    do_expand("case("),
+    do_expand("catch("),
+    do_expand("case ("),
+    do_expand("catch ("),
+
     %% match_arguments coverage
     do_expand("complete_function_parameter:integer_parameter_function(atom,"), %% match_argument -> false
     do_expand("complete_function_parameter:a_zero_arity_fun()"), %% match_argument, parameters empty
diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl
index 86f7ce2fed..e8e79bb9de 100644
--- a/lib/stdlib/test/shell_SUITE.erl
+++ b/lib/stdlib/test/shell_SUITE.erl
@@ -189,11 +189,11 @@ comm_err(<<"ugly().">>),
 comm_err(<<"1 - 2.">>),
 %% Make sure we test all local shell functions in a restricted shell.
 LocalFuncs = shell:local_func(),
-[] = lists:subtract(LocalFuncs, [v,h,b,f,fl,ff,lf,lr,lt,rd,rf,rl,rp,rr,tf,save_module,history,results,catch_exception]),
+[] = lists:subtract(LocalFuncs, [v,h,b,f,fd,fl,ff,lf,lr,lt,rd,rf,rl,rp,rr,tf,save_module,history,results,catch_exception]),
 
 LocalFuncs2 = [
     <<"A = 1.\nv(1).">>, <<"h().">>, <<"b().">>, <<"f().">>, <<"f(A).">>,
-    <<"fl()">>, <<"ff()">>, <<"ff(my_func,1)">>, <<"lf()">>, <<"lr()">>, <<"lt()">>,
+    <<"fl()">>, <<"fd(a, fun(X)->X end,\"a(X)->X.\")">>, <<"ff()">>, <<"ff(my_func,1)">>, <<"lf()">>, <<"lr()">>, <<"lt()">>,
     <<"rd(foo,{bar}).">>, <<"rf().">>, <<"rf(foo).">>, <<"rl().">>, <<"rl(foo).">>, <<"rp([hej]).">>,
     <<"rr(shell).">>, <<"rr(shell, shell_state).">>, <<"rr(shell,shell_state,[]).">>, <<"tf()">>, <<"tf(hej)">>, 
     <<"save_module(\"src/my_module.erl\")">>, <<"history(20).">>, <<"results(20).">>, <<"catch_exception(0).">>],
-- 
2.43.0

openSUSE Build Service is sponsored by