Skip to content

Commit

Permalink
Merge pull request #6279 from garazdawi/lukas/kernel/fix-start_intera…
Browse files Browse the repository at this point in the history
…ctive-to-start-oldshell/OTP-18272/OTP-18271

kernel: Incorporate "oldshell" into user_drv
  • Loading branch information
garazdawi authored Oct 3, 2022
2 parents 919c5b7 + 1ae6b51 commit dc03f02
Show file tree
Hide file tree
Showing 22 changed files with 570 additions and 1,138 deletions.
14 changes: 8 additions & 6 deletions lib/common_test/src/test_server.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2789,7 +2789,8 @@ peer_name(Module, TestCase) ->
peer:random_name(lists:concat([Module, "-", TestCase])).

%% Command line arguments passed
-spec start_peer([string()] | peer:start_options(), atom() | string(), TestCase :: atom() | string()) ->
-spec start_peer([string()] | peer:start_options() | #{ start_cover => boolean() },
atom() | string(), TestCase :: atom() | string()) ->
{ok, gen_statem:server_ref(), node()} | {error, term()}.
start_peer(Args, Module, TestCase) when is_list(Args) ->
start_peer(#{args => Args, name => peer_name(Module, TestCase)}, Module);
Expand All @@ -2801,9 +2802,10 @@ start_peer(Opts, Module, TestCase) ->
start_peer(Opts#{name => peer_name(Module, TestCase)}, Module).

%% Release compatibility testing
-spec start_peer([string()] | peer:start_options(), atom() | string(), TestCase :: atom() | string(),
Release :: string(), OutDir :: file:filename()) ->
{ok, gen_statem:server_ref(), node()} | {error, term()} | not_available.
-spec start_peer([string()] | peer:start_options() | #{ start_cover => boolean() },
atom() | string(), TestCase :: atom() | string(),
Release :: string(), OutDir :: file:filename()) ->
{ok, gen_statem:server_ref(), node()} | {error, term()} | not_available.
start_peer(Args, Module, TestCase, Release, OutDir) when is_list(Args) ->
start_peer(#{args => Args}, Module, TestCase, Release, OutDir);
start_peer(Opts, Module, TestCase, Release, OutDir) ->
Expand All @@ -2815,8 +2817,8 @@ start_peer(Opts, Module, TestCase, Release, OutDir) ->
%% for old releases. Keep ERL_FLAGS, and ERL_ZFLAGS for sometimes you might need it...
Env = maps:get(env, Opts, []) ++ [{"ERL_AFLAGS", false}],
NewArgs = ["-pa", peer_compile(Erl, code:which(peer), OutDir) | maps:get(args, Opts, [])],
start_peer(Opts#{exec => Erl, args => NewArgs,
env => Env}, Module, TestCase)
start_peer(Opts#{exec => Erl, args => NewArgs, env => Env,
start_cover => false }, Module, TestCase)
end.

%% Internal implementation
Expand Down
1 change: 0 additions & 1 deletion lib/kernel/doc/src/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,6 @@ XML_REF3_FILES = application.xml \
seq_trace.xml \
socket.xml \
wrap_log_reader.xml \
user.xml \
zlib_stub.xml \
$(XML_REF3_ESOCK_EFILES)

Expand Down
1 change: 0 additions & 1 deletion lib/kernel/doc/src/kernel_app.xml
Original file line number Diff line number Diff line change
Expand Up @@ -669,7 +669,6 @@ erl -kernel logger '[{handler,default,logger_std_h,#{formatter=>{logger_formatte
<seeerl marker="pg"><c>pg(3)</c></seeerl>,
<seeerl marker="rpc"><c>rpc(3)</c></seeerl>,
<seeerl marker="seq_trace"><c>seq_trace(3)</c></seeerl>,
<seeerl marker="user"><c>user(3)</c></seeerl>,
<seeerl marker="stdlib:timer"><c>timer(3)</c></seeerl></p>
</section>
</appref>
1 change: 0 additions & 1 deletion lib/kernel/doc/src/ref_man.xml
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,6 @@
<xi:include href="rpc.xml"/>
<xi:include href="seq_trace.xml"/>
<xi:include href="socket.xml"/>
<xi:include href="user.xml"/>
<xi:include href="wrap_log_reader.xml"/>
<xi:include href="zlib_stub.xml"/>
</application>
1 change: 0 additions & 1 deletion lib/kernel/doc/src/specs.xml
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,6 @@
<xi:include href="../specs/specs_rpc.xml"/>
<xi:include href="../specs/specs_seq_trace.xml"/>
<xi:include href="../specs/specs_socket.xml"/>
<xi:include href="../specs/specs_user.xml"/>
<xi:include href="../specs/specs_wrap_log_reader.xml"/>
<xi:include href="../specs/specs_zlib_stub.xml"/>
</specs>
41 changes: 0 additions & 41 deletions lib/kernel/doc/src/user.xml

This file was deleted.

3 changes: 1 addition & 2 deletions lib/kernel/src/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -138,10 +138,9 @@ MODULES = \
seq_trace \
socket \
standard_error \
user \
user_drv \
prim_tty \
user_sup \
prim_tty \
raw_file_io \
raw_file_io_compressed \
raw_file_io_inflate \
Expand Down
46 changes: 19 additions & 27 deletions lib/kernel/src/group.erl
Original file line number Diff line number Diff line change
Expand Up @@ -21,8 +21,7 @@

%% A group leader process for user io.

-export([start/2, start/3, server/4]).
-export([interfaces/1]).
-export([start/2, start/3, whereis_shell/0, server/4]).

start(Drv, Shell) ->
start(Drv, Shell, []).
Expand All @@ -49,31 +48,21 @@ server(Ancestors, Drv, Shell, Options) ->
put(expand_fun,ExpandFun),
put(echo, proplists:get_value(echo, Options, true)),

start_shell(Shell),
server_loop(Drv, get(shell), []).
server_loop(Drv, start_shell(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);
_ ->
[]
whereis_shell() ->
case node(group_leader()) of
Node when Node =:= node() ->
case user_drv:whereis_group() of
undefined -> undefined;
GroupPid ->
{dictionary, Dict} = erlang:process_info(GroupPid, dictionary),
proplists:get_value(shell, Dict)
end;
OtherNode ->
erpc:call(OtherNode, group, whereis_shell, [])
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) ->
[].

%% start_shell(Shell)
%% Spawn a shell with its group_leader from the beginning set to ourselves.
%% If Shell a pid the set its group_leader.
Expand All @@ -89,7 +78,8 @@ 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);
put(shell, Shell),
Shell;
start_shell(_Shell) ->
ok.

Expand All @@ -100,7 +90,8 @@ start_shell1(M, F, Args) ->
Shell when is_pid(Shell) ->
group_leader(G, self()),
link(Shell), % we're linked to it.
put(shell, Shell);
put(shell, Shell),
Shell;
Error -> % start failure
exit(Error) % let the group process crash

Expand All @@ -113,7 +104,8 @@ start_shell1(Fun) ->
Shell when is_pid(Shell) ->
group_leader(G, self()),
link(Shell), % we're linked to it.
put(shell, Shell);
put(shell, Shell),
Shell;
Error -> % start failure
exit(Error) % let the group process crash
end.
Expand Down
3 changes: 1 addition & 2 deletions lib/kernel/src/kernel.app.src
Original file line number Diff line number Diff line change
Expand Up @@ -83,9 +83,9 @@
os,
ram_file,
rpc,
user,
user_drv,
user_sup,
prim_tty,
disk_log,
disk_log_1,
disk_log_server,
Expand All @@ -109,7 +109,6 @@
inet_sctp,
pg,
pg2,
prim_tty,
raw_file_io,
raw_file_io_compressed,
raw_file_io_deflate,
Expand Down
46 changes: 29 additions & 17 deletions lib/kernel/src/prim_tty.erl
Original file line number Diff line number Diff line change
Expand Up @@ -104,9 +104,11 @@
%% * Same problem as insert mode, it only deleted current line, and does not move
%% to previous line automatically.

-export([init/1, reinit/2, isatty/1, handles/1, unicode/1, unicode/2, handle_signal/2,
window_size/1, handle_request/2, write/2, write/3, npwcwidth/1, npwcwidthstring/1]).
-export([disable_reader/1, enable_reader/1]).
-export([init/1, reinit/2, isatty/1, handles/1, unicode/1, unicode/2,
handle_signal/2, window_size/1, handle_request/2, write/2, write/3, npwcwidth/1,
npwcwidthstring/1]).
-export([reader_stop/1, disable_reader/1, enable_reader/1]).

-nifs([isatty/1, tty_create/0, tty_init/3, tty_set/1, setlocale/1,
tty_select/3, tty_window_size/1, write_nif/2, read_nif/2, isprint/1,
wcwidth/1, wcswidth/1,
Expand Down Expand Up @@ -182,6 +184,7 @@ on_load(Extra) ->
ok
end.

-spec window_size(state()) -> {ok, {non_neg_integer(), non_neg_integer()}} | {error, term()}.
window_size(State = #state{ tty = TTY }) ->
case tty_window_size(TTY) of
{error, enotsup} when map_get(tty, State#state.options) ->
Expand Down Expand Up @@ -216,8 +219,9 @@ init_term(State = #state{ tty = TTY, options = Options }) ->
case maps:get(tty, Options) of
true ->
ok = tty_init(TTY, stdout, Options),
NewState = init(State, os:type()),
ok = tty_set(TTY),
init(State, os:type());
NewState;
false ->
State
end,
Expand Down Expand Up @@ -254,7 +258,16 @@ options(UserOptions) ->
echo => false }, UserOptions).

init(State, {unix,_}) ->
ok = tgetent(os:getenv("TERM")),

case os:getenv("TERM") of
false ->
error(enotsup);
Term ->
case tgetent(Term) of
ok -> ok;
{error,_} -> error(enotsup)
end
end,

%% See https://www.gnu.org/software/termutils/manual/termcap-1.3/html_mono/termcap.html#SEC23
%% for a list of all possible termcap capabilities
Expand Down Expand Up @@ -346,6 +359,11 @@ unicode(#state{ reader = Reader } = State, Bool) ->
end,
State#state{ unicode = Bool }.

-spec reader_stop(state()) -> state().
reader_stop(#state{ reader = {ReaderPid, _} } = State) ->
{error, _} = call(ReaderPid, stop),
State#state{ reader = undefined }.

-spec handle_signal(state(), winch | cont) -> state().
handle_signal(State, winch) ->
update_geometry(State);
Expand All @@ -354,20 +372,12 @@ handle_signal(State, cont) ->
State.

-spec disable_reader(state()) -> ok.
disable_reader(State) ->
case State#state.reader of
{ReaderPid, _} ->
ok = call(ReaderPid, disable);
undefined -> ok
end.
disable_reader(#state{ reader = {ReaderPid, _} }) ->
ok = call(ReaderPid, disable).

-spec enable_reader(state()) -> ok.
enable_reader(State) ->
case State#state.reader of
{ReaderPid, _} ->
ok = call(ReaderPid, enable);
undefined -> ok
end.
enable_reader(#state{ reader = {ReaderPid, _} }) ->
ok = call(ReaderPid, enable).

call(Pid, Msg) ->
Alias = erlang:monitor(process, Pid, [{alias, reply_demonitor}]),
Expand Down Expand Up @@ -420,6 +430,8 @@ reader_loop(TTY, Parent, SignalRef, ReaderRef, FromEnc, Acc) ->
Alias ! {Alias, FromEnc =/= latin1},
NewFromEnc = if Bool -> utf8; not Bool -> latin1 end,
reader_loop(TTY, Parent, SignalRef, ReaderRef, NewFromEnc, Acc);
{_Alias, stop} ->
ok;
{select, TTY, ReaderRef, ready_input} ->
case read_nif(TTY, ReaderRef) of
{error, closed} ->
Expand Down
Loading

0 comments on commit dc03f02

Please sign in to comment.