File 2924-kernel-Remove-shell-whereis_evaluator.patch of Package erlang
From d289ca2695069d782b62e8a58a566a8aa3c5c769 Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Wed, 11 May 2022 08:04:18 +0200
Subject: [PATCH 04/34] kernel: Remove shell:whereis_evaluator
shell:whereis_evaluator was only used by the pman application
but was not removed when that application was removed.
---
lib/kernel/src/group.erl | 47 ++++++++------------------------
lib/kernel/src/user.erl | 17 ------------
lib/kernel/src/user_drv.erl | 25 -----------------
lib/stdlib/src/shell.erl | 54 -------------------------------------
4 files changed, 11 insertions(+), 132 deletions(-)
diff --git a/lib/kernel/src/group.erl b/lib/kernel/src/group.erl
index 8410c1a4b5..f8ce13e947 100644
--- a/lib/kernel/src/group.erl
+++ b/lib/kernel/src/group.erl
@@ -22,7 +22,6 @@
%% A group leader process for user io.
-export([start/2, start/3, server/3]).
--export([interfaces/1]).
start(Drv, Shell) ->
start(Drv, Shell, []).
@@ -40,31 +39,8 @@ server(Drv, Shell, Options) ->
proplists:get_value(expand_fun, Options,
fun(B) -> edlin_expand:expand(B) end)),
put(echo, proplists:get_value(echo, Options, true)),
-
- start_shell(Shell),
- server_loop(Drv, get(shell), []).
-
-%% Return the pid of user_drv and the shell process.
-%% Note: We can't ask the group process for this info since it
-%% may be busy waiting for data from the driver.
-interfaces(Group) ->
- case process_info(Group, dictionary) of
- {dictionary,Dict} ->
- get_pids(Dict, [], false);
- _ ->
- []
- end.
-get_pids([Drv = {user_drv,_} | Rest], Found, _) ->
- get_pids(Rest, [Drv | Found], true);
-get_pids([Sh = {shell,_} | Rest], Found, Active) ->
- get_pids(Rest, [Sh | Found], Active);
-get_pids([_ | Rest], Found, Active) ->
- get_pids(Rest, Found, Active);
-get_pids([], Found, true) ->
- Found;
-get_pids([], _Found, false) ->
- [].
+ server_loop(Drv, start_shell(Shell), []).
%% start_shell(Shell)
%% Spawn a shell with its group_leader from the beginning set to ourselves.
@@ -81,9 +57,9 @@ start_shell(Shell) when is_function(Shell) ->
start_shell(Shell) when is_pid(Shell) ->
group_leader(self(), Shell), % we are the shells group leader
link(Shell), % we're linked to it.
- put(shell, Shell);
+ Shell;
start_shell(_Shell) ->
- ok.
+ undefined.
start_shell1(M, F, Args) ->
G = group_leader(),
@@ -92,7 +68,7 @@ start_shell1(M, F, Args) ->
Shell when is_pid(Shell) ->
group_leader(G, self()),
link(Shell), % we're linked to it.
- put(shell, Shell);
+ Shell;
Error -> % start failure
exit(Error) % let the group process crash
end.
@@ -104,7 +80,7 @@ start_shell1(Fun) ->
Shell when is_pid(Shell) ->
group_leader(G, self()),
link(Shell), % we're linked to it.
- put(shell, Shell);
+ Shell;
Error -> % start failure
exit(Error) % let the group process crash
end.
@@ -127,7 +103,7 @@ server_loop(Drv, Shell, Buf0) ->
server_loop(Drv, Shell, Buf0);
{'EXIT',Drv,interrupt} ->
%% Send interrupt to the shell.
- exit_shell(interrupt),
+ exit_shell(Shell, interrupt),
server_loop(Drv, Shell, Buf0);
{'EXIT',Drv,R} ->
exit(R);
@@ -143,11 +119,10 @@ server_loop(Drv, Shell, Buf0) ->
server_loop(Drv, Shell, Buf0)
end.
-exit_shell(Reason) ->
- case get(shell) of
- undefined -> true;
- Pid -> exit(Pid, Reason)
- end.
+exit_shell(undefined, _Reason) ->
+ true;
+exit_shell(Pid, Reason) ->
+ exit(Pid, Reason).
get_tty_geometry(Drv) ->
Drv ! {self(),tty_geometry},
@@ -192,7 +167,7 @@ io_request(Req, From, ReplyAs, Drv, Shell, Buf0) ->
%% 'kill' instead of R, since the shell is not always in
%% a state where it is ready to handle a termination
%% message.
- exit_shell(kill),
+ exit_shell(Shell, kill),
exit(R)
end.
diff --git a/lib/kernel/src/user.erl b/lib/kernel/src/user.erl
index 67c2eafdbe..81048922df 100644
--- a/lib/kernel/src/user.erl
+++ b/lib/kernel/src/user.erl
@@ -23,7 +23,6 @@
%% Basic standard i/o server for user interface port.
-export([start/0, start/1, start_out/0]).
--export([interfaces/1]).
-define(NAME, user).
@@ -55,22 +54,6 @@ start_port(PortSettings) ->
register(?NAME, Id),
Id.
-%% Return the pid of the shell process.
-%% Note: We can't ask the user process for this info since it
-%% may be busy waiting for data from the port.
-interfaces(User) ->
- case process_info(User, dictionary) of
- {dictionary,Dict} ->
- case lists:keysearch(shell, 1, Dict) of
- {value,Sh={shell,Shell}} when is_pid(Shell) ->
- [Sh];
- _ ->
- []
- end;
- _ ->
- []
- end.
-
server(Pid) when is_pid(Pid) ->
process_flag(trap_exit, true),
link(Pid),
diff --git a/lib/kernel/src/user_drv.erl b/lib/kernel/src/user_drv.erl
index fa7687bf2a..520dba9419 100644
--- a/lib/kernel/src/user_drv.erl
+++ b/lib/kernel/src/user_drv.erl
@@ -23,8 +23,6 @@
-export([start/0,start/1,start/2,start/3,server/2,server/3]).
--export([interfaces/1]).
-
-include_lib("kernel/include/logger.hrl").
-define(OP_PUTC,0).
@@ -65,26 +63,6 @@ start(Pname, Shell) ->
start(Iname, Oname, Shell) ->
spawn(user_drv, server, [Iname,Oname,Shell]).
-
-%% Return the pid of the active group process.
-%% Note: We can't ask the user_drv process for this info since it
-%% may be busy waiting for data from the port.
-
--spec interfaces(pid()) -> [{'current_group', pid()}].
-
-interfaces(UserDrv) ->
- case process_info(UserDrv, dictionary) of
- {dictionary,Dict} ->
- case lists:keysearch(current_group, 1, Dict) of
- {value,Gr={_,Group}} when is_pid(Group) ->
- [Gr];
- _ ->
- []
- end;
- _ ->
- []
- end.
-
%% server(Pid, Shell)
%% server(Pname, Shell)
%% server(Iname, Oname, Shell)
@@ -147,7 +125,6 @@ server1(Iport, Oport, Shell) ->
{group:start(self(), Shell),Shell}
end,
- put(current_group, Curr),
Gr = gr_add_cur(Gr1, Curr, Shell1),
%% Print some information.
io_request({put_chars, unicode,
@@ -191,7 +168,6 @@ start_user() ->
server_loop(Iport, Oport, User, Gr, IOQueue) ->
Curr = gr_cur_pid(Gr),
- put(current_group, Curr),
server_loop(Iport, Oport, Curr, User, Gr, IOQueue).
server_loop(Iport, Oport, Curr, User, Gr, {Resp, IOQ} = IOQueue) ->
@@ -254,7 +230,6 @@ server_loop(Iport, Oport, Curr, User, Gr, {Resp, IOQ} = IOQueue) ->
Pid1 = group:start(self(), {shell,start,Params}),
{ok,Gr2} = gr_set_cur(gr_set_num(Gr1, Ix, Pid1,
{shell,start,Params}), Ix),
- put(current_group, Pid1),
server_loop(Iport, Oport, Pid1, User, Gr2, IOQueue);
_ -> % remote shell
io_requests([{put_chars,unicode,"(^G to start new job) ***\n"}],
diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl
index 7de78758b0..c3d9c83a66 100644
--- a/lib/stdlib/src/shell.erl
+++ b/lib/stdlib/src/shell.erl
@@ -20,7 +20,6 @@
-module(shell).
-export([start/0, start/1, start/2, server/1, server/2, history/1, results/1]).
--export([whereis_evaluator/0, whereis_evaluator/1]).
-export([start_restricted/1, stop_restricted/0]).
-export([local_allowed/3, non_local_allowed/3]).
-export([catch_exception/1, prompt_func/1, strings/1]).
@@ -62,59 +61,6 @@ start(NoCtrlG, StartSync) ->
_ = code:ensure_loaded(user_default),
spawn(fun() -> server(NoCtrlG, StartSync) end).
-%% Find the pid of the current evaluator process.
--spec whereis_evaluator() -> 'undefined' | pid().
-
-whereis_evaluator() ->
- %% locate top group leader, always registered as user
- %% can be implemented by group (normally) or user
- %% (if oldshell or noshell)
- case whereis(user) of
- undefined ->
- undefined;
- User ->
- %% get user_drv pid from group, or shell pid from user
- case group:interfaces(User) of
- [] -> % old- or noshell
- case user:interfaces(User) of
- [] ->
- undefined;
- [{shell,Shell}] ->
- whereis_evaluator(Shell)
- end;
- [{user_drv,UserDrv}] ->
- %% get current group pid from user_drv
- case user_drv:interfaces(UserDrv) of
- [] ->
- undefined;
- [{current_group,Group}] ->
- %% get shell pid from group
- GrIfs = group:interfaces(Group),
- case lists:keyfind(shell, 1, GrIfs) of
- {shell, Shell} ->
- whereis_evaluator(Shell);
- false ->
- undefined
- end
- end
- end
- end.
-
--spec whereis_evaluator(pid()) -> 'undefined' | pid().
-
-whereis_evaluator(Shell) ->
- case process_info(Shell, dictionary) of
- {dictionary,Dict} ->
- case lists:keyfind(evaluator, 1, Dict) of
- {_, Eval} when is_pid(Eval) ->
- Eval;
- _ ->
- undefined
- end;
- _ ->
- undefined
- end.
-
%% Call this function to start a user restricted shell
%% from a normal shell session.
-spec start_restricted(Module) -> {'error', Reason} when
--
2.35.3