Skip to content

Commit

Permalink
stdlib: Add shell:start_interactive/0,1
Browse files Browse the repository at this point in the history
  • Loading branch information
garazdawi committed Aug 10, 2022
1 parent 1d43051 commit 080996d
Show file tree
Hide file tree
Showing 6 changed files with 138 additions and 10 deletions.
4 changes: 2 additions & 2 deletions erts/doc/src/erl_cmd.xml
Original file line number Diff line number Diff line change
Expand Up @@ -537,12 +537,12 @@ $ <input>erl \
to implement an Alternative Carrier for the Erlang
Distribution</seeguide>.</p>
</item>
<tag><c><![CDATA[-noinput]]></c></tag>
<tag><marker id="noinput"/><c><![CDATA[-noinput]]></c></tag>
<item>
<p>Ensures that the Erlang runtime system never tries to read
any input. Implies <c><![CDATA[-noshell]]></c>.</p>
</item>
<tag><c><![CDATA[-noshell]]></c></tag>
<tag><marker id="noshell"/><c><![CDATA[-noshell]]></c></tag>
<item>
<p>Starts an Erlang runtime system with no shell. This flag
makes it possible to have the Erlang runtime system as a
Expand Down
19 changes: 13 additions & 6 deletions lib/kernel/src/prim_tty.erl
Original file line number Diff line number Diff line change
Expand Up @@ -235,6 +235,8 @@ init_term(State = #state{ tty = TTY, options = Options }) ->
{true, undefined} ->
{ok, Reader} = proc_lib:start_link(?MODULE, reader, [[State#state.tty, self()]]),
WriterState#state{ reader = Reader };
{true, _} ->
WriterState;
{false, undefined} ->
WriterState
end,
Expand Down Expand Up @@ -336,12 +338,17 @@ unicode(State) ->
State#state.unicode.

-spec unicode(state(), boolean()) -> state().
unicode(#state{ reader = {ReaderPid, _} } = State, Bool) ->
MonRef = erlang:monitor(process, ReaderPid),
ReaderPid ! {self(), set_unicode_state, Bool},
receive
{ReaderPid, set_unicode_state, _} -> ok;
{'DOWN',MonRef,_,_,_} -> ok
unicode(#state{ reader = Reader } = State, Bool) ->
case Reader of
{ReaderPid, _} ->
MonRef = erlang:monitor(process, ReaderPid),
ReaderPid ! {self(), set_unicode_state, Bool},
receive
{ReaderPid, set_unicode_state, _} -> ok;
{'DOWN',MonRef,_,_,_} -> ok
end;
undefined ->
ok
end,
State#state{ unicode = Bool }.

Expand Down
7 changes: 5 additions & 2 deletions lib/kernel/src/user_drv.erl
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,7 @@
{requests, [request()]}.

-export_type([message/0]).
-export([start/0, start/1, start_shell/0]).
-export([start/0, start/1, start_shell/0, start_shell/1]).

%% gen_statem state callbacks
-export([init/3,server/3,switch_loop/3]).
Expand Down Expand Up @@ -283,8 +283,11 @@ server({call, From}, {start_shell, Args},
true ->
try prim_tty:reinit(TTY, #{input => maps:get(input, Args, true) }) of
NewTTY ->
#{ read := ReadHandle, write := WriteHandle } = prim_tty:handles(NewTTY),
gen_statem:reply(From, ok),
NewState = State#state{ tty = NewTTY },
NewState = State#state{ tty = NewTTY,
read = ReadHandle,
write = WriteHandle },
case Args of
#{ initial_shell := noshell } ->
init_noshell(NewState);
Expand Down
54 changes: 54 additions & 0 deletions lib/stdlib/doc/src/shell.xml
Original file line number Diff line number Diff line change
Expand Up @@ -956,6 +956,60 @@ q - quit erlang
</desc>
</func>

<func>
<name name="start_interactive" arity="0" since="OTP-12345"/>
<fsummary>Start the interactive shell</fsummary>
<desc>
<p>Starts the interactive shell if it has not already been started.
It can be used to programatically start the shell from an escript
or when erl is started with the -noinput or -noshell flags.</p>
</desc>
</func>

<func>
<name name="start_interactive" arity="1" since="OTP-12345"/>
<fsummary>Start the interactive shell</fsummary>
<desc>
<p>Starts the interactive shell if it has not already been started.
It can be used to programatically start the shell from an
<seecom marker="erts:escript"><c>escript</c></seecom> or when
<seecom marker="erts:erl"><c>erl</c></seecom> is started with the
<seecom marker="erts:erl#noinput"><c>-noinput</c></seecom> or
<seecom marker="erts:erl#noshell"><c>-noshell</c></seecom> flags.
The following options are allowed:</p>
<taglist>
<tag>noshell</tag>
<item>
<p>Starts the interactive shell as if <seecom marker="erts:erl#noshell">
<c>-noshell</c></seecom> was given to <seecom marker="erts:erl"><c>erl</c></seecom>.
This is only useful when erl is started with
<seecom marker="erts:erl#noinput"><c>-noinput</c></seecom> and the
system want to read input data.
</p>
</item>
<tag><seetype marker="erts:erlang#mfa">mfa()</seetype></tag>
<item>
<p>Starts the interactive shell using
<seetype marker="erts:erlang#mfa"><c>mfa()</c></seetype>
as the default shell.</p>
</item>
<tag>{<seetype marker="erts:erlang#node">node()</seetype>,
<seetype marker="erts:erlang#mfa">mfa()</seetype>}</tag>
<item>
<p>Starts the interactive shell using
<seetype marker="erts:erlang#mfa"><c>mfa()</c></seetype> on
<seetype marker="erts:erlang#node"><c>node()</c></seetype> as the default shell.</p>
</item>
<tag>{remote, <seetype marker="erts:erlang#string"><c>string()</c></seetype>}</tag>
<item>
<p>Starts the interactive shell using as if
<seecom marker="erts:erl#remsh"><c>-remsh</c></seecom>
was given to <seecom marker="erts:erl"><c>erl</c></seecom>.</p>
</item>
</taglist>
</desc>
</func>

<func>
<name name="start_restricted" arity="1" since=""/>
<fsummary>Exit a normal shell and starts a restricted shell.</fsummary>
Expand Down
11 changes: 11 additions & 0 deletions lib/stdlib/src/shell.erl
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@
-export([start_restricted/1, stop_restricted/0]).
-export([local_allowed/3, non_local_allowed/3]).
-export([catch_exception/1, prompt_func/1, strings/1]).
-export([start_interactive/0, start_interactive/1]).

-define(LINEMAX, 30).
-define(CHAR_MAX, 60).
Expand All @@ -47,6 +48,16 @@ non_local_allowed({init,stop},[],State) ->
non_local_allowed(_,_,State) ->
{false,State}.

-spec start_interactive() -> ok | {error, already_started | enottty}.
start_interactive() ->
user_drv:start_shell().
-spec start_interactive(noshell | mfa() | {node(), mfa()} | {remote, string()}) ->
ok | {error, already_started | enottty}.
start_interactive({Node, {_M,_F,_A}}) ->
start_interactive({Node, _M,_F,_A});
start_interactive(InitialShell) ->
user_drv:start_shell(#{ initial_shell => InitialShell }).

-spec start() -> pid().

start() ->
Expand Down
53 changes: 53 additions & 0 deletions lib/stdlib/test/shell_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,8 @@
-export([ start_restricted_from_shell/1,
start_restricted_on_command_line/1,restricted_local/1]).

-export([ start_interactive/1 ]).

%% Internal export.
-export([otp_5435_2/0, prompt1/1, prompt2/1, prompt3/1, prompt4/1,
prompt5/1]).
Expand Down Expand Up @@ -3014,6 +3016,57 @@ otp_14296(Config) when is_list(Config) ->
{error, {_,_,"bad term"}} = TF("1, 2"),
ok.

start_interactive(_Config) ->
rtnode:run(
[{expect, "test"},
{putline, "test."},
{eval, fun() -> shell:start_interactive() end},
{expect, "1>"},
{expect, "2>"}
],[],"",["-noinput","-eval","io:format(\"test~n\")"]),

rtnode:run(
[{expect, "test"},
{putline, "test."},
{eval, fun() -> shell:start_interactive({shell,start,[]}) end},
{expect, "1>"},
{expect, "2>"}
],[],"",["-noinput","-eval","io:format(\"test~n\")"]),

rtnode:run(
[{expect, "test"},
{putline, "test."},
{eval, fun() -> shell:start_interactive(noshell) end},
{eval, fun() -> io:format(user,"~ts",[io:get_line(user, "")]) end},
{expect, "test\\."},
{putline, "test."},
{eval, fun() -> shell:start_interactive() end},
{expect, "1>"},
{expect, "2>"}
],[],"",["-noinput","-eval","io:format(\"test~n\")"]),

{ok, RPeer, RNode} = ?CT_PEER(),
unlink(RPeer),
SRNode = atom_to_list(RNode),
rtnode:run(
[{expect, "test"},
{putline, "test."},
{eval, fun() -> shell:start_interactive({remote, SRNode}) end},
{expect, "\\Q("++SRNode++")\\E2>"}
],[],"",["-noinput","-eval","io:format(\"test~n\")"]),

{ok, Peer, Node} = ?CT_PEER(),
unlink(Peer),
SNode = atom_to_list(Node),
rtnode:run(
[{expect, "test"},
{putline, "test."},
{eval, fun() -> shell:start_interactive({Node, {shell,start,[]}}) end},
{expect, "\\Q("++SNode++")\\E2>"}
],[],"",["-noinput","-eval","io:format(\"test~n\")"]),

ok.

term_to_string(T) ->
lists:flatten(io_lib:format("~w", [T])).

Expand Down

0 comments on commit 080996d

Please sign in to comment.