File 3387-kernel-Refactor-group-to-use-gen_statem-and-less-pro.patch of Package erlang
From 5315cf0ca55f7a05e30b5664892e39621b3f5cf4 Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Fri, 30 Aug 2024 10:50:02 +0200
Subject: [PATCH 7/8] kernel: Refactor group to use gen_statem and less process
dictionary
---
lib/kernel/src/group.erl | 1465 ++++++++++---------
lib/kernel/src/user_drv.erl | 76 +-
lib/kernel/test/interactive_shell_SUITE.erl | 2 +-
lib/ssh/src/ssh_cli.erl | 7 +-
lib/stdlib/src/io_lib.erl | 14 +-
5 files changed, 810 insertions(+), 754 deletions(-)
diff --git a/lib/kernel/src/group.erl b/lib/kernel/src/group.erl
index f256b2fd2d..d886c001fc 100644
--- a/lib/kernel/src/group.erl
+++ b/lib/kernel/src/group.erl
@@ -28,55 +28,136 @@
%% It then keeps that data as unicode in its state and converts it
%% to latin1/unicode on a per request basis. If any data is left after
%% a request, that data is again kept as unicode.
-
--export([start/2, start/3, whereis_shell/0, server/4]).
-
--export([server_loop/3]).
-
+%%
+%% There are two major modes of group that work in similar though subtly different
+%% ways, xterm and dumb. The xterm mode is used when a "newshell" is used and dumb
+%% is used when "oldshell" or "noshell" are used.
+
+-export([start/1, start/2, start/3, whereis_shell/0, init/3, server/3,
+ xterm/3, dumb/3, handle_info/3]).
+
+%% gen statem callbacks
+-export([init/1, callback_mode/0]).
+
+-type mfargs() :: {module(), atom(), [term()]}.
+-type nmfargs() :: {node(), module(), atom(), [term()]}.
+
+-define(IS_PUTC_REQ(Req), element(1, Req) =:= put_chars orelse element(1, Req) =:= requests).
+-define(IS_INPUT_REQ(Req),
+ element(1, Req) =:= get_chars orelse element(1, Req) =:= get_line orelse
+ element(1, Req) =:= get_until orelse element(1, Req) =:= get_password).
+
+-record(input_state,
+ {
+ %% Used by all input routines
+ from,
+ reply_as,
+ prompt_bytes,
+ encoding,
+ collect,
+ cont,
+
+ %% Used by xterm state
+ lines = [], %% Previously entered lines that have not yet been consumed
+
+ %% used by dumb state
+ get_fun,
+ io_lib_state = start
+ }).
+
+-record(state,
+ { read_mode :: list | binary,
+ driver :: pid(),
+ echo :: boolean(),
+ dumb :: boolean(),
+ shell = noshell :: noshell | pid(),
+
+ %% Only used by xterm
+ line_history :: [string()] | undefined,
+ expand_fun :: function() | undefined,
+ expand_below :: boolean() | undefined,
+
+ %% Used to push details about a input requests
+ %% if there are multiple ones in progress.
+ input_queue = queue:new(),
+
+ %% Keeps extra data inbetween input routines
+ buf = [] :: unicode:chardata() | eof,
+
+ input = undefined :: #input_state{} | undefined
+ }).
+
+-spec start(pid()) -> pid().
+start(Drv) ->
+ start(Drv, noshell).
+-spec start(pid(), function() | nmfargs() | mfargs() | noshell) -> pid().
start(Drv, Shell) ->
start(Drv, Shell, []).
+-spec start(pid(), function() | nmfargs() | mfargs() | noshell,
+ [{name, atom()} |
+ {dumb, boolean()} |
+ {echo, boolean()} |
+ {expand_fun, function()} |
+ {expand_below, boolean()}]) -> pid().
start(Drv, Shell, Options) ->
- Ancestors = [self() | case get('$ancestors') of
- undefined -> [];
- Anc -> Anc
- end],
- spawn_link(group, server, [Ancestors, Drv, Shell, Options]).
+ {ok, Pid} =
+ case proplists:get_value(name, Options) of
+ undefined ->
+ gen_statem:start(?MODULE, [Drv, Shell, Options], []);
+ Name ->
+ gen_statem:start({local, Name}, ?MODULE, [Drv, Shell, Options], [])
+ end,
+ Pid.
-server(Ancestors, Drv, Shell, Options) ->
+callback_mode() -> state_functions.
+
+init([Drv, Shell, Options]) ->
process_flag(trap_exit, true),
- _ = [put('$ancestors', Ancestors) || Shell =/= {}],
- edlin:init(),
- put(read_mode, list),
- put(user_drv, Drv),
- ExpandFun = normalize_expand_fun(Options, fun edlin_expand:expand/2),
- put(expand_fun, ExpandFun),
+ %% Cleanup ancestors so that observer looks nice
+ _ = [put('$ancestors',tl(get('$ancestors'))) || Shell =:= noshell],
- %% echo can be set to false by -oldshell and ssh_cli
- put(echo, proplists:get_value(echo, Options, true)),
+ %% We link here instead of using start_link so that Drv does not become our parent
+ %% We don't want Drv as our parent as Drv will send EXIT signals to us and we need
+ %% to handle those and not just terminate.
+ link(Drv),
- %% dumb can be set to true by ssh_cli
- put(dumb, proplists:get_value(dumb, Options, false)),
+ Dumb = proplists:get_value(dumb, Options, Shell =:= noshell),
- %% noshell can be set to true by user_drv
- put(noshell, proplists:get_value(noshell, Options, false)),
+ State = #state{
+ driver = Drv,
+ read_mode = list,
+ dumb = Dumb,
- %% expand_below can be set by user_drv and ssh_cli
- put(expand_below, proplists:get_value(expand_below, Options, true)),
+ %% echo is normally false for dumb and true for non-dumb, but when group is used by
+ %% ssh, it can also be set to true when dumb is true.
+ echo = proplists:get_value(echo, Options, not Dumb)
- DefaultGroupHistory =
- case not get(echo) of
- true ->
- [];
- false ->
- group_history:load()
- end,
+ },
- put(line_buffer, proplists:get_value(line_buffer, Options, DefaultGroupHistory)),
+ edlin:init(),
+
+ {ok, init, State, {next_event, internal, [Shell, Options]}}.
+
+init(internal, [Shell, Options], State = #state{ dumb = Dumb }) ->
- server_loop(Drv, start_shell(Shell), []).
+ StartedShell = start_shell(Shell),
+
+ NonDumbState =
+ if not Dumb ->
+ State#state{
+ line_history = group_history:load(),
+ expand_below = proplists:get_value(expand_below, Options, not Dumb),
+ expand_fun = normalize_expand_fun(Options, fun edlin_expand:expand/2)
+ };
+ Dumb ->
+ State
+ end,
+ {next_state, server, NonDumbState#state{ shell = StartedShell }}.
+
+-spec whereis_shell() -> undefined | pid().
whereis_shell() ->
case node(group_leader()) of
Node when Node =:= node() ->
@@ -94,92 +175,331 @@ whereis_shell() ->
%% Spawn a shell with its group_leader from the beginning set to ourselves.
%% If Shell a pid the set its group_leader.
+-spec start_shell(mfargs() | nmfargs() |
+ module() | function() | pid() | noshell) -> pid() | noshell.
+start_shell(noshell) -> noshell;
start_shell({Mod,Func,Args}) ->
- start_shell1(Mod, Func, Args);
+ start_shell_mfa(Mod, Func, Args);
start_shell({Node,Mod,Func,Args}) ->
- start_shell1(rpc, call, [Node,Mod,Func,Args]);
+ start_shell_mfa(erpc, call, [Node,Mod,Func,Args]);
start_shell(Shell) when is_atom(Shell) ->
- start_shell1(Shell, start, []);
+ start_shell_mfa(Shell, start, []);
start_shell(Shell) when is_function(Shell) ->
- start_shell1(Shell);
+ start_shell_fun(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.
+ 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.
+ proc_lib:set_label({group, Shell}),
+ Shell.
-start_shell1(M, F, Args) ->
+start_shell_mfa(M, F, Args) ->
G = group_leader(),
group_leader(self(), self()),
- case catch apply(M, F, Args) of
- Shell when is_pid(Shell) ->
- group_leader(G, self()),
- link(Shell), % we're linked to it.
- put(shell, Shell),
+ case apply(M, F, Args) of
+ Shell when is_pid(Shell) ->
+ group_leader(G, self()),
+ link(Shell), % we're linked to it.
+ proc_lib:set_label({group, {M, F, Args}}),
+ put(shell, Shell),
Shell;
- Error -> % start failure
- exit(Error) % let the group process crash
+ Error -> % start failure
+ exit(Error) % let the group process crash
end.
-start_shell1(Fun) ->
+start_shell_fun(Fun) ->
G = group_leader(),
group_leader(self(), self()),
- case catch Fun() of
- Shell when is_pid(Shell) ->
- group_leader(G, self()),
- link(Shell), % we're linked to it.
- put(shell, Shell),
+ case Fun() of
+ Shell when is_pid(Shell) ->
+ group_leader(G, self()),
+ link(Shell), % we're linked to it.
+ proc_lib:set_label({group, Fun}),
+ put(shell, Shell),
Shell;
- Error -> % start failure
- exit(Error) % let the group process crash
+ Error -> % start failure
+ exit(Error) % let the group process crash
end.
--spec server_loop(UserDrv :: pid(), Shell:: pid(),
- Buffer :: unicode:chardata()) ->
- no_return().
-server_loop(Drv, Shell, Buf0) ->
- receive
- {io_request,From,ReplyAs,Req} when is_pid(From) ->
- %% This io_request may cause a transition to a couple of
- %% selective receive loops elsewhere in this module.
- Buf = io_request(Req, From, ReplyAs, Drv, Shell, Buf0),
- ?MODULE:server_loop(Drv, Shell, Buf);
- {reply,{From,ReplyAs},Reply} ->
- io_reply(From, ReplyAs, Reply),
- ?MODULE:server_loop(Drv, Shell, Buf0);
- {driver_id,ReplyTo} ->
- ReplyTo ! {self(),driver_id,Drv},
- ?MODULE:server_loop(Drv, Shell, Buf0);
- {Drv, echo, Bool} ->
- put(echo, Bool),
- ?MODULE:server_loop(Drv, Shell, Buf0);
- {'EXIT',Drv,interrupt} ->
- %% Send interrupt to the shell.
- exit_shell(interrupt),
- ?MODULE:server_loop(Drv, Shell, Buf0);
- {'EXIT',Drv,R} ->
- exit(R);
- {'EXIT',Shell,R} ->
- exit(R);
- %% We want to throw away any term that we don't handle (standard
- %% practice in receive loops), but not any {Drv,_} tuples which are
- %% handled in io_request/6.
- NotDrvTuple when (not is_tuple(NotDrvTuple)) orelse
- (tuple_size(NotDrvTuple) =/= 2) orelse
- (element(1, NotDrvTuple) =/= Drv) ->
- %% Ignore this unknown message.
- ?MODULE:server_loop(Drv, Shell, Buf0)
- end.
+%% When there are no outstanding input requests we are in this state
+server(info, {io_request,From,ReplyAs,Req}, Data) when is_pid(From), ?IS_INPUT_REQ(Req) ->
+ {next_state,
+ if Data#state.dumb orelse not Data#state.echo -> dumb; true -> xterm end,
+ Data#state{ input = #input_state{ from = From, reply_as = ReplyAs } },
+ {next_event, internal, Req}};
+server(info, {Drv, echo, Bool}, Data = #state{ driver = Drv }) ->
+ {keep_state, Data#state{ echo = Bool }};
+server(info, {Drv, _}, #state{ driver = Drv }) ->
+ %% We postpone any Drv event sent to us as they are handled in xterm or dumb states
+ {keep_state_and_data, postpone};
+server(info, Msg, Data) ->
+ handle_info(server, Msg, Data).
+
+%% This is the dumb terminal state, also used for noshell and xterm get_password
+dumb(internal, {get_chars, Encoding, Prompt, N}, Data) ->
+ dumb(input_request, {collect_chars, N, Prompt, Encoding, fun get_chars_dumb/5}, Data);
+dumb(internal, {get_line, Encoding, Prompt}, Data) ->
+ dumb(input_request, {collect_line, [], Prompt, Encoding, fun get_line_dumb/5}, Data);
+dumb(internal, {get_until, Encoding, Prompt, M, F, As}, Data) ->
+ dumb(input_request, {get_until, {M, F, As}, Prompt, Encoding, fun get_line_dumb/5}, Data);
+dumb(internal, {get_password, _Encoding}, Data) ->
+ %% TODO: Implement for noshell by disabling characters echo if isatty(stdin)
+ io_reply(Data, {error, enotsup}),
+ pop_state(Data);
+dumb(input_request, {CollectF, CollectAs, Prompt, Encoding, GetFun},
+ Data = #state{ input = OrigInputState }) ->
+
+ InputState = OrigInputState#input_state{
+ prompt_bytes = prompt_bytes(Prompt, Encoding),
+ collect = {CollectF, CollectAs},
+ encoding = Encoding, get_fun = GetFun },
+
+ dumb(data, Data#state.buf, Data#state{ input = InputState, buf = [] });
+
+%% If we get an input request while handling this request we push the current state
+%% and re-issue event in server state
+dumb(info, {io_request, _From, _ReplyAs, Req}, Data) when ?IS_INPUT_REQ(Req) ->
+ {next_state, server, push_state(dumb, Data), [{postpone, true}]};
+dumb(internal, restore_input_request, Data = #state{ buf = Buf }) ->
+ dumb(data, Buf, Data#state{ buf = [] });
+
+dumb(data, Buf, Data = #state{ input = #input_state{ prompt_bytes = Pbs, encoding = Encoding,
+ io_lib_state = State, cont = Cont,
+ collect = {CollectF, CollectAs},
+ get_fun = GetFun } = InputState }) ->
+
+ %% Get a single line using get_line_dumb, or a single character using get_chars_dumb
+ case GetFun(Buf, Pbs, Cont, Encoding, Data) of
+ {no_translation, unicode, latin1} ->
+ io_reply(Data, {error,{no_translation, unicode, latin1}}),
+ pop_state(Data#state{ buf = [] });
+ {done, NewLine, RemainBuf} ->
+ EncodedLine = cast(NewLine, Data#state.read_mode, Encoding),
+ case io_lib:CollectF(State, EncodedLine, Encoding, CollectAs) of
+ {stop, eof, _} ->
+ io_reply(Data, eof),
+ pop_state(Data#state{ buf = eof });
+ {stop, Result, eof} ->
+ io_reply(Data, Result),
+ pop_state(Data#state{ buf = eof });
+ {stop, Result, Rest} ->
+ io_reply(Data, Result),
+ pop_state(Data#state{ buf = append(Rest, RemainBuf, Encoding) });
+ {'EXIT',_} ->
+ io_reply(Data, {error,err_func(io_lib, CollectF, CollectAs)}),
+ pop_state(Data#state{ buf = [] });
+ NewState ->
+ dumb(data, RemainBuf, Data#state{ input = InputState#input_state{ cont = undefined, io_lib_state = NewState } })
+ end;
+ {more_chars, NewCont} ->
+ {keep_state, Data#state{ input = InputState#input_state{ cont = NewCont } } }
+ end;
+
+dumb(info, {Drv, activate}, #state{ driver = Drv }) ->
+ keep_state_and_data;
+dumb(info, Msg, Data) ->
+ handle_info(dumb, Msg, Data).
+
+%% The xterm state handles the "newshell" mode. This is the most advanced shell
+%% that has a shell history, can open text editors and navigate in multiline shell
+%% expressions.
+xterm(internal, {get_chars, Encoding, Prompt, N}, Data) ->
+ xterm(input_request, {collect_chars, N, Prompt, Encoding}, Data);
+xterm(internal, {get_line, Encoding, Prompt}, Data) ->
+ xterm(input_request, {collect_line, [], Prompt, Encoding}, Data);
+xterm(internal, {get_until, Encoding, Prompt, M, F, As}, Data) ->
+ xterm(input_request, {get_until, {M, F, As}, Prompt, Encoding}, Data);
+xterm(internal, {get_password, Encoding}, Data) ->
+
+ %% When getting the password we change state to dumb and use its
+ %% implementation and set echo to false.
+ GetLine = fun(Buf, Pbs, Cont, LineEncoding, LineData) ->
+ get_line_dumb(Buf, Pbs, Cont, LineEncoding,
+ LineData#state{ echo = false })
+ end,
+ case dumb(input_request, {collect_line_no_eol, [], "", Encoding, GetLine}, Data) of
+ {keep_state, NewData} ->
+ %% As we are currently in the xterm state, we transition to dumb
+ {next_state, dumb, NewData};
+ Else when element(1, Else) =:= next_state -> Else
+ end;
+xterm(input_request, {CollectF, CollectAs, Prompt, Encoding},
+ Data = #state{ input = OrigInputState }) ->
+
+ InputState = OrigInputState#input_state{
+ prompt_bytes = prompt_bytes(Prompt, Encoding),
+ collect = {CollectF, CollectAs},
+ encoding = Encoding },
+
+ xterm(data, Data#state.buf, Data#state{ input = InputState, buf = [] });
+
+xterm(info, {io_request, _From, _ReplyAs, Req}, Data = #state{ driver = Drv })
+ when ?IS_INPUT_REQ(Req) ->
+ %% We got an new input request while serving this one, we:
+ %% * erase current line
+ %% * push the current input state
+ %% * re-issue the input event in the server state
+ send_drv_reqs(Drv, edlin:erase_line()),
+ {next_state, server, push_state(xterm, Data), [{postpone, true}]};
+xterm(internal, restore_input_request,
+ #state{ buf = Buf, driver = Drv, input = #input_state{ cont = {EdlinCont, _} }} = Data) ->
+ %% We are restoring an input request so we redraw the line
+ send_drv_reqs(Drv, edlin:redraw_line(EdlinCont)),
+ xterm(data, Buf, Data#state{ buf = [] });
+
+xterm(data, Buf, Data = #state{ input = #input_state{
+ prompt_bytes = Pbs, encoding = Encoding,
+ lines = Lines, cont = Cont,
+ collect = {CollectF, CollectAs} } = InputState }) ->
+
+ %% Get a single line using edlin
+ case get_line_edlin(Buf, Pbs, Cont, Lines, Encoding, Data) of
+ {done, NewLines, RemainBuf} ->
+ CurrentLine = cast(edlin:current_line(NewLines), Data#state.read_mode, Encoding),
+ case io_lib:CollectF(start, CurrentLine, Encoding, CollectAs) of
+ {stop, eof, _} ->
+ io_reply(Data, eof),
+ pop_state(Data#state{ buf = eof });
+ {stop, Result, eof} ->
+ io_reply(Data, Result),
+ pop_state(Data#state{ buf = eof });
+ {stop, Result, Rest} ->
+ %% Prompt was valid expression, clear the prompt in user_drv and redraw
+ %% the formatted expression.
+ FormattedLine = format_expression(NewLines, Data#state.driver),
+ [CL1|LB1] = lists:reverse(string:split(FormattedLine, "\n", all)),
+ LineCont1 = {LB1,{lists:reverse(CL1++"\n"), []},[]},
+ MultiLinePrompt = lists:duplicate(shell:prompt_width(Pbs), $\s),
+ send_drv_reqs(Data#state.driver, [{redraw_prompt, Pbs, MultiLinePrompt, LineCont1},new_prompt]),
+
+ NewHistory =
+ %% TODO: Change to allow client to set whether to save commands
+ %% using io:setopts instead.
+ if CollectF =:= get_until ->
+ %% Save into history buffer if issued from shell process
+ save_line_buffer(string:trim(FormattedLine, both)++"\n",
+ Data#state.line_history);
+ true ->
+ Data#state.line_history
+ end,
+
+ io_reply(Data, Result),
+ pop_state(
+ Data#state{ line_history = NewHistory,
+ buf = append(Rest, RemainBuf, Encoding) });
+ {'EXIT',_} ->
+ io_reply(Data, {error,err_func(io_lib, CollectF, CollectAs)}),
+ pop_state(Data#state{ buf = [] });
+ _M ->
+ xterm(data, RemainBuf, Data#state{ input = InputState#input_state{ cont = undefined, lines = NewLines} })
+ end;
+ {blink, NewCont} ->
+ {keep_state, Data#state{ input = InputState#input_state{ cont = NewCont } }, 1000};
+ {more_chars, NewCont} ->
+ {keep_state, Data#state{ input = InputState#input_state{ cont = NewCont } } }
+ end;
-exit_shell(Reason) ->
- case get(shell) of
- undefined -> true;
- Pid -> exit(Pid, Reason)
+xterm(info, {io_request,From,ReplyAs,Req},
+ Data = #state{ driver = Drv, input = #input_state{ cont = {EdlinCont, _} } })
+ when ?IS_PUTC_REQ(Req) ->
+ send_drv_reqs(Drv, edlin:erase_line()),
+ putc_request(Req, From, ReplyAs, Data#state.driver),
+ send_drv_reqs(Drv, edlin:redraw_line(EdlinCont)),
+ keep_state_and_data;
+
+xterm(info, {Drv, activate},
+ #state{ driver = Drv, input = #input_state{ cont = {EdlinCont, _} } }) ->
+ send_drv_reqs(Drv, edlin:redraw_line(EdlinCont)),
+ keep_state_and_data;
+
+xterm(info, Msg, Data) ->
+ handle_info(xterm, Msg, Data);
+
+xterm(timeout, 1000, Data) ->
+ %% Blink timeout triggered
+ xterm(data, [], Data).
+
+%% Handle the info messages that needs to be managed in all states
+handle_info(State, {Drv, {data, Buf}}, Data = #state{ driver = Drv }) ->
+ ?MODULE:State(data, Buf, Data);
+handle_info(State, {Drv, eof}, Data = #state{ driver = Drv }) ->
+ ?MODULE:State(data, eof, Data);
+
+handle_info(_State, {io_request, From, ReplyAs, {setopts, Opts}}, Data) ->
+ {Reply, NewData} = setopts(Opts, Data),
+ io_reply(From, ReplyAs, Reply),
+ {keep_state, NewData};
+handle_info(_State, {io_request,From,ReplyAs, getopts}, Data) ->
+ io_reply(From, ReplyAs, getopts(Data)),
+ keep_state_and_data;
+handle_info(_State, {io_request,From,ReplyAs, {get_geometry, What}}, Data) ->
+ case get_tty_geometry(Data#state.driver) of
+ {Width, _Height} when What =:= columns->
+ io_reply(From, ReplyAs, Width);
+ {_Width, Height} when What =:= rows->
+ io_reply(From, ReplyAs, Height);
+ _ ->
+ io_reply(From, ReplyAs, {error, enotsup})
+ end,
+ keep_state_and_data;
+handle_info(_State, {io_request,From,ReplyAs,Req}, Data) when ?IS_PUTC_REQ(Req) ->
+ putc_request(Req, From, ReplyAs, Data#state.driver);
+
+handle_info(_State, {reply, undefined, _Reply}, _Data) ->
+ %% Ignore any reply with an undefined From.
+ keep_state_and_data;
+handle_info(_State, {reply,{From,ReplyAs},Reply}, _Data) ->
+ io_reply(From, ReplyAs, Reply),
+ keep_state_and_data;
+
+handle_info(_State, {driver_id,ReplyTo}, Data) -> %% TODO: Remove this?
+ ReplyTo ! {self(),driver_id, Data#state.driver},
+ keep_state_and_data;
+handle_info(_State, {'EXIT', Drv, interrupt}, #state{ driver = Drv, shell = Shell, input = undefined }) ->
+ %% Send interrupt to the shell of there is no current input request
+ [exit(Shell, interrupt) || is_pid(Shell)],
+ keep_state_and_data;
+handle_info(_State, {'EXIT', Drv, interrupt}, #state{ driver = Drv } = Data) ->
+ %% Interrupt current input request
+ io_reply(Data, {error, interrupted}),
+ pop_state(Data#state{ buf = [] });
+
+handle_info(_State, {'EXIT',Drv,R}, #state{ driver = Drv } = Data) ->
+ [ exit(Data#state.shell, kill)
+ || is_pid(Data#state.shell) andalso Data#state.input =/= undefined],
+ {stop, R};
+handle_info(_State, {'EXIT',Shell,R}, #state{ shell = Shell, driver = Drv }) ->
+ %% We propagate the error reason from the shell to the driver, but we don't
+ %% want to exit ourselves with that reason as it will generate crash report
+ %% messages that we do not want.
+ exit(Drv, R),
+ {stop, normal};
+
+handle_info(_State, _UnknownEvent, _Data) ->
+ %% Ignore this unknown message.
+ erlang:display({unknown, _UnknownEvent}),
+ ok = _UnknownEvent,
+ keep_state_and_data.
+
+%% When we get an input request while already serving another, we
+%% push the state of the current request into the input_queue and
+%% switch to handling the new request.
+push_state(State, Data) ->
+ Data#state{ input_queue = queue:in({State, Data#state.input}, Data#state.input_queue) }.
+
+%% When an input request is done we then need to check if there was
+%% another request in progress, and if so we pop its state and resume it.
+pop_state(Data) ->
+ case queue:out(Data#state.input_queue) of
+ {empty, _} ->
+ {next_state, server, Data#state{ input = undefined }};
+ {{value, {State, InputState}}, NewInputQueue} ->
+ {next_state, State, Data#state{ input = InputState, input_queue = NewInputQueue },
+ {next_event, internal, restore_input_request } }
end.
+%% Functions for getting data from the driver
get_tty_geometry(Drv) ->
Drv ! {self(),tty_geometry},
receive
@@ -210,168 +530,124 @@ set_unicode_state(Drv,Bool) ->
get_terminal_state(Drv) ->
Drv ! {self(),get_terminal_state},
receive
- {Drv,get_terminal_state,Terminal} ->
- Terminal;
- {Drv,get_terminal_state,error} ->
- {error, internal}
+ {Drv,get_terminal_state,Terminal} ->
+ Terminal;
+ {Drv,get_terminal_state,error} ->
+ {error, internal}
after 2000 ->
- {error,timeout}
+ {error,timeout}
end.
-io_request(Req, From, ReplyAs, Drv, Shell, Buf0) ->
- case io_request(Req, Drv, Shell, {From,ReplyAs}, Buf0) of
- {ok,Reply,Buf} ->
- io_reply(From, ReplyAs, Reply),
- Buf;
- {noreply,Buf} ->
+%% This function handles any put_chars request
+putc_request(Req, From, ReplyAs, Drv) ->
+ case putc_request(Req, Drv, {From, ReplyAs}) of
+ {reply,Reply} ->
+ io_reply(From, ReplyAs, Reply),
+ keep_state_and_data;
+ noreply ->
%% We expect a {reply,_} message from the Drv when request is done
- Buf;
- {error,Reply,Buf} ->
- io_reply(From, ReplyAs, Reply),
- Buf;
- {exit,R} ->
- %% '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(R)
+ keep_state_and_data
end.
-
%% Put_chars, unicode is the normal message, characters are always in
%% standard unicode format.
%% You might be tempted to send binaries unchecked, but the driver
%% expects unicode, so that is what we should send...
-%% io_request({put_chars,unicode,Binary}, Drv, Buf) when is_binary(Binary) ->
+%% putc_request({put_chars,unicode,Binary}, Drv, Buf) when is_binary(Binary) ->
%% send_drv(Drv, {put_chars,Binary}),
%% {ok,ok,Buf};
%%
%% These put requests have to be synchronous to the driver as otherwise
%% there is no guarantee that the data has actually been printed.
-io_request({put_chars,unicode,Chars}, Drv, _Shell, From, Buf) ->
+putc_request({put_chars,unicode,Chars}, Drv, From) ->
case catch unicode:characters_to_binary(Chars,utf8) of
- Binary when is_binary(Binary) ->
- send_drv(Drv, {put_chars_sync, unicode, Binary, From}),
- {noreply,Buf};
- _ ->
- {error,{error,{put_chars, unicode,Chars}},Buf}
+ Binary when is_binary(Binary) ->
+ send_drv(Drv, {put_chars_sync, unicode, Binary, From}),
+ noreply;
+ _ ->
+ {reply,{error,{put_chars, unicode,Chars}}}
end;
-io_request({put_chars,unicode,M,F,As}, Drv, _Shell, From, Buf) ->
+putc_request({put_chars,unicode,M,F,As}, Drv, From) ->
case catch apply(M, F, As) of
- Binary when is_binary(Binary) ->
- send_drv(Drv, {put_chars_sync, unicode, Binary, From}),
- {noreply,Buf};
- Chars ->
- case catch unicode:characters_to_binary(Chars,utf8) of
- B when is_binary(B) ->
- send_drv(Drv, {put_chars_sync, unicode, B, From}),
- {noreply,Buf};
- _ ->
- {error,{error,F},Buf}
- end
+ Binary when is_binary(Binary) ->
+ send_drv(Drv, {put_chars_sync, unicode, Binary, From}),
+ noreply;
+ Chars ->
+ case catch unicode:characters_to_binary(Chars,utf8) of
+ B when is_binary(B) ->
+ send_drv(Drv, {put_chars_sync, unicode, B, From}),
+ noreply;
+ _ ->
+ {reply,{error,F}}
+ end
end;
-io_request({put_chars,latin1,Binary}, Drv, _Shell, From, Buf) when is_binary(Binary) ->
+putc_request({put_chars,latin1,Binary}, Drv, From) when is_binary(Binary) ->
send_drv(Drv, {put_chars_sync, unicode,
unicode:characters_to_binary(Binary,latin1),
From}),
- {noreply,Buf};
-io_request({put_chars,latin1,Chars}, Drv, _Shell, From, Buf) ->
+ noreply;
+putc_request({put_chars,latin1,Chars}, Drv, From) ->
case catch unicode:characters_to_binary(Chars,latin1) of
Binary when is_binary(Binary) ->
send_drv(Drv, {put_chars_sync, unicode, Binary, From}),
- {noreply,Buf};
+ noreply;
_ ->
- {error,{error,{put_chars,latin1,Chars}},Buf}
+ {reply,{error,{put_chars,latin1,Chars}}}
end;
-io_request({put_chars,latin1,M,F,As}, Drv, _Shell, From, Buf) ->
+putc_request({put_chars,latin1,M,F,As}, Drv, From) ->
case catch apply(M, F, As) of
- Binary when is_binary(Binary) ->
- send_drv(Drv, {put_chars_sync, unicode,
+ Binary when is_binary(Binary) ->
+ send_drv(Drv, {put_chars_sync, unicode,
unicode:characters_to_binary(Binary,latin1),
From}),
- {noreply,Buf};
- Chars ->
- case catch unicode:characters_to_binary(Chars,latin1) of
- B when is_binary(B) ->
- send_drv(Drv, {put_chars_sync, unicode, B, From}),
- {noreply,Buf};
- _ ->
- {error,{error,F},Buf}
- end
+ noreply;
+ Chars ->
+ case catch unicode:characters_to_binary(Chars,latin1) of
+ B when is_binary(B) ->
+ send_drv(Drv, {put_chars_sync, unicode, B, From}),
+ noreply;
+ _ ->
+ {reply,{error,F}}
+ end
end;
-io_request({get_chars,Encoding,Prompt,N}, Drv, Shell, _From, Buf) ->
- get_chars_n(Prompt, io_lib, collect_chars, N, Drv, Shell, Buf, Encoding);
-io_request({get_line,Encoding,Prompt}, Drv, Shell, _From, Buf) ->
- get_chars_line(Prompt, io_lib, collect_line, [], Drv, Shell, Buf, Encoding);
-io_request({get_until,Encoding, Prompt,M,F,As}, Drv, Shell, _From, Buf) ->
- get_chars_line(Prompt, io_lib, get_until, {M,F,As}, Drv, Shell, Buf, Encoding);
-io_request({get_password,_Encoding},Drv,Shell,_From,Buf) ->
- get_password_chars(Drv, Shell, Buf);
-io_request({setopts,Opts}, Drv, _Shell, _From, Buf) when is_list(Opts) ->
- setopts(Opts, Drv, Buf);
-io_request(getopts, Drv, _Shell, _From, Buf) ->
- getopts(Drv, Buf);
-io_request({requests,Reqs}, Drv, Shell, From, Buf) ->
- io_requests(Reqs, {ok,ok,Buf}, From, Drv, Shell);
-
-%% New in R12
-io_request({get_geometry,columns},Drv,_Shell,_From,Buf) ->
- case get_tty_geometry(Drv) of
- {W,_H} ->
- {ok,W,Buf};
- _ ->
- {error,{error,enotsup},Buf}
- end;
-io_request({get_geometry,rows},Drv,_Shell,_From,Buf) ->
- case get_tty_geometry(Drv) of
- {_W,H} ->
- {ok,H,Buf};
- _ ->
- {error,{error,enotsup},Buf}
- end;
+putc_request({requests,Reqs}, Drv, From) ->
+ putc_requests(Reqs, {reply, ok}, Drv, From);
%% BC with pre-R13
-io_request({put_chars,Chars}, Drv, Shell, From, Buf) ->
- io_request({put_chars,latin1,Chars}, Drv, Shell, From, Buf);
-io_request({put_chars,M,F,As}, Drv, Shell, From, Buf) ->
- io_request({put_chars,latin1,M,F,As}, Drv, Shell, From, Buf);
-io_request({get_chars,Prompt,N}, Drv, Shell, From, Buf) ->
- io_request({get_chars,latin1,Prompt,N}, Drv, Shell, From, Buf);
-io_request({get_line,Prompt}, Drv, Shell, From, Buf) ->
- io_request({get_line,latin1,Prompt}, Drv, Shell, From, Buf);
-io_request({get_until, Prompt,M,F,As}, Drv, Shell, From, Buf) ->
- io_request({get_until,latin1, Prompt,M,F,As}, Drv, Shell, From, Buf);
-io_request(get_password,Drv,Shell,From,Buf) ->
- io_request({get_password,latin1},Drv,Shell,From,Buf);
-
+putc_request({put_chars,Chars}, Drv, From) ->
+ putc_request({put_chars,latin1,Chars}, Drv, From);
+putc_request({put_chars,M,F,As}, Drv, From) ->
+ putc_request({put_chars,latin1,M,F,As}, Drv, From);
+putc_request(_, _Drv, _From) ->
+ {error,{error,request}}.
-io_request(_, _Drv, _Shell, _From, Buf) ->
- {error,{error,request},Buf}.
-
-%% Status = io_requests(RequestList, PrevStat, From, Drv, Shell)
+%% Status = putc_requests(RequestList, PrevStat, From, Drv, Shell)
%% Process a list of output requests as long as
%% the previous status is 'ok' or noreply.
%%
%% We use undefined as the From for all but the last request
%% in order to discards acknowledgements from those requests.
%%
-io_requests([R|Rs], {noreply,Buf}, From, Drv, Shell) ->
+putc_requests([R|Rs], noreply, Drv, From) ->
ReqFrom = if Rs =:= [] -> From; true -> undefined end,
- io_requests(Rs, io_request(R, Drv, Shell, ReqFrom, Buf), From, Drv, Shell);
-io_requests([R|Rs], {ok,ok,Buf}, From, Drv, Shell) ->
+ putc_requests(Rs, putc_request(R, Drv, ReqFrom), Drv, From);
+putc_requests([R|Rs], {reply,ok}, Drv, From) ->
ReqFrom = if Rs =:= [] -> From; true -> undefined end,
- io_requests(Rs, io_request(R, Drv, Shell, ReqFrom, Buf), From, Drv, Shell);
-io_requests([_|_], Error, _From, _Drv, _Shell) ->
+ putc_requests(Rs, putc_request(R, Drv, ReqFrom), Drv, From);
+putc_requests([_|_], Error, _Drv, _From) ->
Error;
-io_requests([], Stat, _From, _, _Shell) ->
+putc_requests([], Stat, _Drv, _From) ->
Stat.
%% io_reply(From, ReplyAs, Reply)
%% The function for sending i/o command acknowledgement.
%% The ACK contains the return value.
+io_reply(#state{ input = #input_state{ from = From, reply_as = As } }, Reply) ->
+ io_reply(From, As, Reply).
+
io_reply(undefined, _ReplyAs, _Reply) ->
%% Ignore these replies as they are generated from io_requests/5.
ok;
@@ -399,16 +675,16 @@ expand_encoding([unicode | T]) ->
expand_encoding([H|T]) ->
[H|expand_encoding(T)].
%% setopts
-setopts(Opts0,Drv,Buf) ->
+setopts(Opts0,Data) ->
Opts = proplists:unfold(
- proplists:substitute_negations(
- [{list,binary}],
- expand_encoding(Opts0))),
+ proplists:substitute_negations(
+ [{list,binary}],
+ expand_encoding(Opts0))),
case check_valid_opts(Opts) of
- true ->
- do_setopts(Opts,Drv,Buf);
- false ->
- {error,{error,enotsup},Buf}
+ true ->
+ do_setopts(Opts,Data);
+ false ->
+ {{error,enotsup},Data}
end.
check_valid_opts([]) ->
true;
@@ -426,180 +702,62 @@ check_valid_opts([{expand_fun,Fun}|T]) when is_function(Fun, 1);
check_valid_opts(_) ->
false.
-do_setopts(Opts, Drv, Buf) ->
- put(expand_fun, normalize_expand_fun(Opts, get(expand_fun))),
- put(echo, proplists:get_value(echo, Opts, get(echo))),
+do_setopts(Opts, Data) ->
+ ExpandFun = normalize_expand_fun(Opts, Data#state.expand_fun),
+ Echo = proplists:get_value(echo, Opts, Data#state.echo),
case proplists:get_value(encoding, Opts) of
- Valid when Valid =:= unicode; Valid =:= utf8 ->
- set_unicode_state(Drv,true);
- latin1 ->
- set_unicode_state(Drv,false);
- undefined ->
- ok
+ Valid when Valid =:= unicode; Valid =:= utf8 ->
+ set_unicode_state(Data#state.driver,true);
+ latin1 ->
+ set_unicode_state(Data#state.driver,false);
+ undefined ->
+ ok
end,
- case proplists:get_value(binary, Opts, case get(read_mode) of
- binary -> true;
- _ -> false
- end) of
- true ->
- put(read_mode, binary),
- {ok,ok,Buf};
- false ->
- put(read_mode, list),
- {ok,ok,Buf}
- end.
+ ReadMode =
+ case proplists:get_value(binary, Opts,
+ case Data#state.read_mode of
+ binary -> true;
+ _ -> false
+ end) of
+ true ->
+ binary;
+ false ->
+ list
+ end,
+ {ok, Data#state{ expand_fun = ExpandFun, echo = Echo, read_mode = ReadMode}}.
normalize_expand_fun(Options, Default) ->
case proplists:get_value(expand_fun, Options, Default) of
- Fun when is_function(Fun, 1) -> fun(X,_) -> Fun(X) end;
- Fun -> Fun
+ Fun when is_function(Fun, 1) -> fun(X,_) -> Fun(X) end;
+ Fun -> Fun
end.
-getopts(Drv,Buf) ->
- Exp = {expand_fun, case get(expand_fun) of
- Func when is_function(Func) ->
- Func;
- _ ->
- false
- end},
- Echo = {echo, case get(echo) of
- Bool when Bool =:= true; Bool =:= false ->
- Bool;
- _ ->
- false
- end},
- Bin = {binary, case get(read_mode) of
- binary ->
- true;
- _ ->
- false
- end},
- Uni = {encoding, case get_unicode_state(Drv) of
- true -> unicode;
- _ -> latin1
- end},
- Terminal = get_terminal_state(Drv),
+getopts(Data) ->
+ Exp = {expand_fun, case Data#state.expand_fun of
+ Func when is_function(Func) ->
+ Func;
+ _ ->
+ false
+ end},
+ Echo = {echo, case Data#state.echo of
+ Bool when Bool =:= true; Bool =:= false ->
+ Bool;
+ _ ->
+ false
+ end},
+ Bin = {binary, case Data#state.read_mode of
+ binary ->
+ true;
+ _ ->
+ false
+ end},
+ Uni = {encoding, case get_unicode_state(Data#state.driver) of
+ true -> unicode;
+ _ -> latin1
+ end},
+ Terminal = get_terminal_state(Data#state.driver),
Tty = {terminal, maps:get(stdout, Terminal)},
- {ok,[Exp,Echo,Bin,Uni,Tty|maps:to_list(Terminal)],Buf}.
-
-%% get_chars_*(Prompt, Module, Function, XtraArgument, Drv, Buffer)
-%% Gets characters from the input Drv until as the applied function
-%% returns {stop,Result,Rest}. Does not block output until input has been
-%% received.
-%% Returns:
-%% {Result,NewSaveBuffer}
-%% {error,What,NewSaveBuffer}
-
-get_password_chars(Drv,Shell,Buf) ->
- case get(echo) of
- true ->
- case get_password_line(Buf, Drv, Shell) of
- {done, Line, Buf1} ->
- {ok, Line, Buf1};
- interrupted ->
- {error, {error, interrupted}, []};
- terminated ->
- {exit, terminated}
- end;
- false ->
- %% Echo needs to be set to true, otherwise the
- %% password will be printed to the shell and we
- %% do not want that.
- {error, {error, enotsup}, []}
- end.
-
-get_chars_n(Prompt, M, F, Xa, Drv, Shell, Buf, Encoding) ->
- Pbs = prompt_bytes(Prompt, Encoding),
- case get(echo) of
- true ->
- get_chars_loop(Pbs, M, F, Xa, Drv, Shell, Buf, start, [], Encoding);
- false ->
- get_chars_n_loop(Pbs, M, F, Xa, Drv, Shell, Buf, start, Encoding)
- end.
-
-get_chars_line(Prompt, M, F, Xa, Drv, Shell, Buf, Encoding) ->
- Pbs = prompt_bytes(Prompt, Encoding),
- get_chars_loop(Pbs, M, F, Xa, Drv, Shell, Buf, start, [], Encoding).
-
-get_chars_loop(Pbs, M, F, Xa, Drv, Shell, Buf0, State, LineCont0, Encoding) ->
- Result = case not(get(dumb)) andalso get(echo) of
- true ->
- get_line(Buf0, Pbs, LineCont0, Drv, Shell, Encoding);
- false ->
- get_line_echo_off(Buf0, Encoding, Pbs, Drv, Shell)
- end,
- case Result of
- {done,LineCont1,Buf} ->
- get_chars_apply(Pbs, M, F, Xa, Drv, Shell, append(Buf, [], Encoding),
- State, LineCont1, Encoding);
- {no_translation, unicode, latin1} ->
- {error,{error,{no_translation, unicode, latin1}}, []};
- interrupted ->
- {error,{error,interrupted},[]};
- terminated ->
- {exit,terminated}
- end.
-
-get_chars_apply(Pbs, M, F, Xa, Drv, Shell, Buf, State0, LineCont, Encoding) ->
- %% multi line support means that we should not keep the state
- %% but we need to keep it for oldshell mode
- {State, Line} = case not(get(dumb)) andalso get(echo) of
- true -> {start, edlin:current_line(LineCont)};
- false -> {State0, LineCont}
- end,
- case catch M:F(State, cast(Line,get(read_mode), Encoding), Encoding, Xa) of
- {stop,eof,_} ->
- {ok,eof,eof};
- {stop,Result,eof} ->
- {ok,Result,eof};
- {stop,Result,Rest} ->
- %% Prompt was valid expression, clear the prompt in user_drv
- %% First redraw without the multi line prompt
- FormattedLine = format_expression(LineCont, Drv),
- case LineCont of
- {[_|_], _, _} ->
- [CL1|LB1] = lists:reverse(string:split(FormattedLine, "\n", all)),
- LineCont1 = {LB1,{lists:reverse(CL1++"\n"), []},[]},
- MultiLinePrompt = lists:duplicate(shell:prompt_width(Pbs), $\s),
- send_drv_reqs(Drv, [{redraw_prompt, Pbs, MultiLinePrompt, LineCont1},new_prompt]);
- _ -> skip %% oldshell mode
- end,
- _ = case {M,F} of
- {io_lib, get_until} ->
- save_line_buffer(string:trim(FormattedLine, both)++"\n", get_lines(new_stack(get(line_buffer))));
- _ ->
- skip
- end,
- {ok,Result,append(Rest, Buf, Encoding)};
- {'EXIT',_} ->
- {error,{error,err_func(M, F, Xa)},[]};
- State1 ->
- get_chars_loop(Pbs, M, F, Xa, Drv, Shell, Buf, State1, LineCont, Encoding)
- end.
-
-get_chars_n_loop(Pbs, M, F, Xa, Drv, Shell, Buf0, State, Encoding) ->
- case check_encoding(Buf0, Encoding) of
- false ->
- {error,{error,{no_translation,unicode,Encoding}},[]};
- true ->
- try M:F(State, cast(Buf0, get(read_mode), Encoding), Encoding, Xa) of
- {stop,eof,_} ->
- {ok, eof, eof};
- {stop,Result,Rest} ->
- {ok, Result, append(Rest,[],Encoding)};
- State1 ->
- case get_chars_echo_off(Pbs, Drv, Shell) of
- interrupted ->
- {error,{error,interrupted},[]};
- terminated ->
- {exit,terminated};
- Buf ->
- get_chars_n_loop(Pbs, M, F, Xa, Drv, Shell, Buf, State1, Encoding)
- end
- catch _:_ ->
- {error,{error,err_func(M, F, Xa)},[]}
- end
- end.
+ [Exp,Echo,Bin,Uni,Tty|maps:to_list(Terminal)].
%% Convert error code to make it look as before
err_func(io_lib, get_until, {_,F,_}) ->
@@ -608,24 +766,37 @@ err_func(_, F, _) ->
F.
%% get_line(Chars, PromptBytes, Drv)
-%% Get a line with eventual line editing. Handle other io requests
-%% while getting line.
+%% Get a line with eventual line editing.
%% Returns:
%% {done,LineChars,RestChars}
-%% interrupted
-get_line(Chars, Pbs, Cont, Drv, Shell, Encoding) ->
- {more_chars,Cont1,Rs} = case Cont of
+%% {more_data, Cont, Ls}
+%% {blink, Cons, Ls}
+
+-record(get_line_edlin_state, {history, encoding, expand_fun, expand_below,
+ search, search_quit_prompt, search_result}).
+
+get_line_edlin(Chars, Pbs, undefined, Lines, Encoding,
+ #state{ driver = Drv, line_history = History,
+ expand_fun = ExpandFun, expand_below = ExpandBelow}) ->
+ {more_chars,Cont1,Rs} = case Lines of
[] -> edlin:start(Pbs);
- _ -> edlin:start(Pbs, Cont)
+ _ -> edlin:start(Pbs, Lines)
end,
send_drv_reqs(Drv, Rs),
- get_line1(edlin:edit_line(Chars, Cont1), Drv, Shell, new_stack(get(line_buffer)),
- Encoding).
-
-get_line1({done, Cont, Rest, Rs}, Drv, _Shell, _Ls, _Encoding) ->
+ get_line_edlin(edlin:edit_line(Chars, Cont1), Drv, #get_line_edlin_state{
+ history = new_stack(History),
+ encoding = Encoding,
+ expand_fun = ExpandFun,
+ expand_below = ExpandBelow });
+get_line_edlin(Chars, _Pbs, {EdlinCont, GetLineState}, _Lines, _Encoding,
+ #state{ driver = Drv }) ->
+ get_line_edlin(edlin:edit_line(cast(Chars, list), EdlinCont),
+ Drv, GetLineState).
+
+get_line_edlin({done, Cont, Rest, Rs}, Drv, _State) ->
send_drv_reqs(Drv, Rs),
{done, Cont, Rest};
-get_line1({open_editor, _Cs, Cont, Rs}, Drv, Shell, Ls0, Encoding) ->
+get_line_edlin({open_editor, _Cs, Cont, Rs}, Drv, State) ->
send_drv_reqs(Drv, Rs),
Buffer = edlin:current_line(Cont),
send_drv(Drv, {open_editor, Buffer}),
@@ -634,52 +805,50 @@ get_line1({open_editor, _Cs, Cont, Rs}, Drv, Shell, Ls0, Encoding) ->
send_drv_reqs(Drv, edlin:erase_line()),
{more_chars,NewCont,NewRs} = edlin:start(edlin:prompt(Cont)),
send_drv_reqs(Drv, NewRs),
- get_line1(edlin:edit_line(Cs1, NewCont), Drv, Shell, Ls0, Encoding)
+ get_line_edlin(edlin:edit_line(Cs1, NewCont), Drv, State)
end;
-get_line1({format_expression, _Cs, {line, _, _, _} = Cont, Rs}, Drv, Shell, Ls, Encoding) ->
+get_line_edlin({format_expression, _Cs, {line, _, _, _} = Cont, Rs}, Drv, State) ->
send_drv_reqs(Drv, Rs),
Cs1 = format_expression(Cont, Drv),
send_drv_reqs(Drv, edlin:erase_line()),
{more_chars,NewCont,NewRs} = edlin:start(edlin:prompt(Cont)),
send_drv_reqs(Drv, NewRs),
- get_line1(edlin:edit_line(Cs1, NewCont), Drv, Shell, Ls, Encoding);
+ get_line_edlin(edlin:edit_line(Cs1, NewCont), Drv, State);
%% Move Up, Down in History: Ctrl+P, Ctrl+N
-get_line1({history_up,Cs,{_,_,_,Mode0}=Cont,Rs}, Drv, Shell, Ls0, Encoding) ->
+get_line_edlin({history_up,Cs,{_,_,_,Mode0}=Cont,Rs}, Drv, State) ->
send_drv_reqs(Drv, Rs),
- case up_stack(save_line(Ls0, edlin:current_line(Cont))) of
+ case up_stack(save_line(State#get_line_edlin_state.history, edlin:current_line(Cont))) of
{none,_Ls} ->
send_drv(Drv, beep),
- get_line1(edlin:edit_line(Cs, Cont), Drv, Shell, Ls0, Encoding);
+ get_line_edlin(edlin:edit_line(Cs, Cont), Drv, State);
{Lcs,Ls} ->
send_drv_reqs(Drv, edlin:erase_line()),
{more_chars,{A,B,C,_},Nrs} = edlin:start(edlin:prompt(Cont)),
Ncont = {A,B,C,Mode0},
send_drv_reqs(Drv, Nrs),
- get_line1(
+ get_line_edlin(
edlin:edit_line1(
string:to_graphemes(
lists:sublist(Lcs, 1, length(Lcs)-1)),
Ncont),
- Drv, Shell, Ls, Encoding)
+ Drv, State#get_line_edlin_state{ history = Ls })
end;
-get_line1({history_down,Cs,{_,_,_,Mode0}=Cont,Rs}, Drv, Shell, Ls0, Encoding) ->
+get_line_edlin({history_down,Cs,{_,_,_,Mode0}=Cont,Rs}, Drv, State) ->
send_drv_reqs(Drv, Rs),
- case down_stack(save_line(Ls0, edlin:current_line(Cont))) of
+ case down_stack(save_line(State#get_line_edlin_state.history, edlin:current_line(Cont))) of
{none,_Ls} ->
send_drv(Drv, beep),
- get_line1(edlin:edit_line(Cs, Cont), Drv, Shell, Ls0, Encoding);
+ get_line_edlin(edlin:edit_line(Cs, Cont), Drv, State);
{Lcs,Ls} ->
send_drv_reqs(Drv, edlin:erase_line()),
{more_chars,{A,B,C,_},Nrs} = edlin:start(edlin:prompt(Cont)),
Ncont = {A,B,C,Mode0},
send_drv_reqs(Drv, Nrs),
- get_line1(edlin:edit_line1(string:to_graphemes(lists:sublist(Lcs,
- 1,
- length(Lcs)-1)),
- Ncont),
- Drv,
- Shell,
- Ls, Encoding)
+ get_line_edlin(edlin:edit_line1(string:to_graphemes(lists:sublist(Lcs,
+ 1,
+ length(Lcs)-1)),
+ Ncont),
+ Drv, State#get_line_edlin_state{ history = Ls })
end;
%% ^R = backward search, ^S = forward search.
%% Search is tricky to implement and does a lot of back-and-forth
@@ -691,62 +860,61 @@ get_line1({history_down,Cs,{_,_,_,Mode0}=Cont,Rs}, Drv, Shell, Ls0, Encoding) ->
%% new modes: search, search_quit, search_found. These are added to
%% the regular ones (none, meta_left_sq_bracket) and handle special
%% cases of history search.
-get_line1({search,Cs,Cont,Rs}, Drv, Shell, Ls, Encoding) ->
+get_line_edlin({search,Cs,Cont,Rs}, Drv, State) ->
send_drv_reqs(Drv, Rs),
%% drop current line, move to search mode. We store the current
%% prompt ('N>') and substitute it with the search prompt.
- put(search_quit_prompt, Cont),
- Pbs = prompt_bytes("\033[;1;4msearch:\033[0m ", Encoding),
+ Pbs = prompt_bytes("\033[;1;4msearch:\033[0m ", State#get_line_edlin_state.encoding),
{more_chars,Ncont,_Nrs} = edlin:start(Pbs, {search,none}),
- put(search, new_search),
- get_line1(edlin:edit_line1(Cs, Ncont), Drv, Shell, Ls, Encoding);
-get_line1({help, Before, Cs0, Cont, Rs}, Drv, Shell, Ls0, Encoding) ->
+ get_line_edlin(edlin:edit_line1(Cs, Ncont), Drv,
+ State#get_line_edlin_state{ search = new_search,
+ search_quit_prompt = Cont});
+get_line_edlin({help, Before, Cs0, Cont, Rs}, Drv, State) ->
send_drv_reqs(Drv, Rs),
{_,Word,_} = edlin:over_word(Before, [], 0),
{R,Docs} = case edlin_context:get_context(Before) of
- {function, Mod} when Word =/= [] -> try
- {ok, [{atom,_,Module}], _} = erl_scan:string(Mod),
- {ok, [{atom,_,Word1}], _} = erl_scan:string(Word),
- {function, c:h1(Module, Word1)}
- catch _:_ ->
- {ok, [{atom,_,Module1}], _} = erl_scan:string(Mod),
- {module, c:h1(Module1)}
- end;
- {function, Mod} ->
- {ok, [{atom,_,Module}], _} = erl_scan:string(Mod),
- {module, c:h1(Module)};
- {function, Mod, Fun, _Args, _Unfinished, _Nesting} ->
- {ok, [{atom,_,Module}], _} = erl_scan:string(Mod),
- {ok, [{atom,_,Function}], _} = erl_scan:string(Fun),
- {function, c:h1(Module, Function)};
- {term, _, {atom, Word1}}->
- {ok, [{atom,_,Module}], _} = erl_scan:string(Word1),
- {module, c:h1(Module)};
- _ -> {error, {error, no_help}}
- end,
+ {function, Mod} when Word =/= [] -> try
+ {ok, [{atom,_,Module}], _} = erl_scan:string(Mod),
+ {ok, [{atom,_,Word1}], _} = erl_scan:string(Word),
+ {function, c:h1(Module, Word1)}
+ catch _:_ ->
+ {ok, [{atom,_,Module1}], _} = erl_scan:string(Mod),
+ {module, c:h1(Module1)}
+ end;
+ {function, Mod} ->
+ {ok, [{atom,_,Module}], _} = erl_scan:string(Mod),
+ {module, c:h1(Module)};
+ {function, Mod, Fun, _Args, _Unfinished, _Nesting} ->
+ {ok, [{atom,_,Module}], _} = erl_scan:string(Mod),
+ {ok, [{atom,_,Function}], _} = erl_scan:string(Fun),
+ {function, c:h1(Module, Function)};
+ {term, _, {atom, Word1}}->
+ {ok, [{atom,_,Module}], _} = erl_scan:string(Word1),
+ {module, c:h1(Module)};
+ _ -> {error, {error, no_help}}
+ end,
case {R, Docs} of
{_, {error, _}} -> send_drv(Drv, beep);
{module, _} ->
- Docs1 = " "++string:trim(lists:nthtail(3, Docs),both),
- send_drv(Drv, {put_expand, unicode,
- [unicode:characters_to_binary(Docs1)], 7});
+ Docs1 = " "++string:trim(lists:nthtail(3, Docs),both),
+ send_drv(Drv, {put_expand, unicode,
+ [unicode:characters_to_binary(Docs1)], 7});
{function, _} ->
- Docs1 = " "++string:trim(Docs,both),
- send_drv(Drv, {put_expand, unicode,
- [unicode:characters_to_binary(Docs1)], 7})
+ Docs1 = " "++string:trim(Docs,both),
+ send_drv(Drv, {put_expand, unicode,
+ [unicode:characters_to_binary(Docs1)], 7})
end,
- get_line1(edlin:edit_line(Cs0, Cont), Drv, Shell, Ls0, Encoding);
-get_line1({Expand, Before, Cs0, Cont,Rs}, Drv, Shell, Ls0, Encoding)
+ get_line_edlin(edlin:edit_line(Cs0, Cont), Drv, State);
+get_line_edlin({Expand, Before, Cs0, Cont,Rs}, Drv, State = #get_line_edlin_state{ expand_fun = ExpandFun })
when Expand =:= expand; Expand =:= expand_full ->
send_drv_reqs(Drv, Rs),
- ExpandFun = get(expand_fun),
{Found, CompleteChars, Matches} = ExpandFun(Before, []),
case Found of
no -> send_drv(Drv, beep);
_ -> ok
end,
{Width, _Height} = get_tty_geometry(Drv),
- Cs1 = append(CompleteChars, Cs0, Encoding),
+ Cs1 = append(CompleteChars, Cs0, State#get_line_edlin_state.encoding),
MatchStr = case Matches of
[] -> [];
@@ -758,65 +926,62 @@ get_line1({Expand, Before, Cs0, Cont,Rs}, Drv, Shell, Ls0, Encoding)
_ ->
NlMatchStr = unicode:characters_to_binary("\n"++MatchStr),
NLines = case Expand of
- expand -> 7;
- expand_full -> 0
- end,
- case get(expand_below) of
+ expand -> 7;
+ expand_full -> 0
+ end,
+ case State#get_line_edlin_state.expand_below of
true ->
- send_drv(Drv, {put_expand, unicode, unicode:characters_to_binary(string:trim(MatchStr, trailing)), NLines}),
- Cs1;
+ send_drv(Drv, {put_expand, unicode, unicode:characters_to_binary(string:trim(MatchStr, trailing)), NLines}),
+ Cs1;
false ->
send_drv(Drv, {put_chars, unicode, NlMatchStr}),
[$\e, $l | Cs1]
end
end,
- get_line1(edlin:edit_line(Cs, Cont), Drv, Shell, Ls0, Encoding);
+ get_line_edlin(edlin:edit_line(Cs, Cont), Drv, State);
%% The search item was found and accepted (new line entered on the exact
%% result found)
-get_line1({search_found,_Cs,_,Rs}, Drv, Shell, Ls0, Encoding) ->
- SearchResult = get(search_result),
- LineCont = case SearchResult of
+get_line_edlin({search_found,_Cs,_,Rs}, Drv, State) ->
+ LineCont = case State#get_line_edlin_state.search_result of
[] -> {[],{[],[]},[]};
- _ -> [Last| LB] = lists:reverse(SearchResult),
- {LB, {lists:reverse(Last),[]},[]}
+ SearchResult ->
+ [Last| LB] = lists:reverse(SearchResult),
+ {LB, {lists:reverse(Last),[]},[]}
end,
- Prompt = edlin:prompt(get(search_quit_prompt)),
+ Prompt = edlin:prompt(State#get_line_edlin_state.search_quit_prompt),
send_drv_reqs(Drv, Rs),
send_drv_reqs(Drv, edlin:erase_line()),
send_drv_reqs(Drv, edlin:redraw_line({line, Prompt, LineCont, {normal,none}})),
- put(search_result, []),
- get_line1({done, LineCont, "\n", Rs}, Drv, Shell, Ls0, Encoding);
+ get_line_edlin({done, LineCont, "\n", Rs}, Drv, State#get_line_edlin_state{ search_result = []});
%% The search mode has been exited, but the user wants to remain in line
%% editing mode wherever that was, but editing the search result.
-get_line1({search_quit,_Cs,_,Rs}, Drv, Shell, Ls, Encoding) ->
+get_line_edlin({search_quit,_Cs,_,Rs}, Drv, State) ->
%% Load back the old prompt with the correct line number.
- case edlin:prompt(get(search_quit_prompt)) of
+ case edlin:prompt(State#get_line_edlin_state.search_quit_prompt) of
Prompt -> % redraw the line and keep going with the same stack position
- SearchResult = get(search_result),
- L = case SearchResult of
+ L = case State#get_line_edlin_state.search_result of
[] -> {[],{[],[]},[]};
- _ -> [Last|LB] = lists:reverse(SearchResult),
- {LB, {lists:reverse(Last), []}, []}
+ SearchResult ->
+ [Last|LB] = lists:reverse(SearchResult),
+ {LB, {lists:reverse(Last), []}, []}
end,
NCont = {line,Prompt,L,{normal,none}},
- put(search_result, []),
send_drv_reqs(Drv, [delete_line|Rs]),
send_drv_reqs(Drv, edlin:redraw_line(NCont)),
- get_line1({more_chars, NCont ,[]}, Drv, Shell, pad_stack(Ls), Encoding)
+ get_line_edlin({more_chars, NCont ,[]}, Drv,
+ State#get_line_edlin_state{ history = pad_stack(State#get_line_edlin_state.history),
+ search_result = [] })
end;
-get_line1({search_cancel,_Cs,_,Rs}, Drv, Shell, Ls, Encoding) ->
- NCont = get(search_quit_prompt),
- put(search_result, []),
+get_line_edlin({search_cancel,_Cs,_,Rs}, Drv, State = #get_line_edlin_state{ search_quit_prompt = NCont }) ->
send_drv_reqs(Drv, [delete_line|Rs]),
send_drv_reqs(Drv, edlin:redraw_line(NCont)),
- get_line1({more_chars, NCont, []}, Drv, Shell, Ls, Encoding);
+ get_line_edlin({more_chars, NCont, []}, Drv, State#get_line_edlin_state{ search_result = [] });
%% Search mode is entered.
-get_line1({What,{line,Prompt,{_,{RevCmd0,_},_},{search, none}}=Cont0,Rs},
- Drv, Shell, Ls0, Encoding) ->
+get_line_edlin({What,{line,Prompt,{_,{RevCmd0,_},_},{search, none}}=Cont0,Rs},
+ Drv, State = #get_line_edlin_state{ search = OldSearch, history = Ls0 }) ->
%% Figure out search direction. ^S and ^R are returned through edlin
%% whenever we received a search while being already in search mode.
- OldSearch = get(search),
{Search, Ls1, RevCmd} = case RevCmd0 of
[$\^S|RevCmd1] ->
{fun search_down_stack/2, Ls0, RevCmd1};
@@ -827,140 +992,34 @@ get_line1({What,{line,Prompt,{_,{RevCmd0,_},_},{search, none}}=Cont0,Rs},
_ ->
{skip, Ls0, RevCmd0}
end,
- put(search, RevCmd),
Cmd = lists:reverse(RevCmd),
if Search =:= skip ->
- %% Move expand are the only valid requests to bypass search mode
- %% Sending delete_chars, insert_chars, etc. will result in
- %% expand area being cleared.
- Rs1 = [R||{move_expand,_}=R<-Rs],
- send_drv_reqs(Drv, Rs1),
- more_data(What, Cont0, Drv, Shell, Ls0, Encoding);
+ %% Move expand are the only valid requests to bypass search mode
+ %% Sending delete_chars, insert_chars, etc. will result in
+ %% expand area being cleared.
+ Rs1 = [R||{move_expand,_}=R<-Rs],
+ send_drv_reqs(Drv, Rs1),
+ {What, {Cont0, State#get_line_edlin_state{ search = RevCmd }}};
true ->
- {Ls, NewStack} = case Search(Ls1, Cmd) of
- {none, Ls2} ->
- send_drv(Drv, beep),
- put(search_result, []),
- send_drv(Drv, delete_line),
- send_drv(Drv, {insert_chars, unicode, unicode:characters_to_binary(Prompt++Cmd)}),
- {Ls2, {[],{RevCmd, []},[]}};
- {Line, Ls2} -> % found. Complete the output edlin couldn't have done.
- Lines = string:split(string:to_graphemes(Line), "\n", all),
- put(search_result, Lines),
- send_drv(Drv, delete_line),
- send_drv(Drv, {insert_chars, unicode, unicode:characters_to_binary(Prompt++Cmd)}),
- send_drv(Drv, {put_expand, unicode, unicode:characters_to_binary(" "++lists:join("\n ",Lines)), 7}),
- {Ls2, {[],{RevCmd, []},[]}}
- end,
- Cont = {line,Prompt,NewStack,{search, none}},
- more_data(What, Cont, Drv, Shell, Ls, Encoding)
+ {Ls, SearchResult, NewStack} = case Search(Ls1, Cmd) of
+ {none, Ls2} ->
+ send_drv(Drv, beep),
+ send_drv(Drv, delete_line),
+ send_drv(Drv, {insert_chars, unicode, unicode:characters_to_binary(Prompt++Cmd)}),
+ {Ls2, [], {[],{RevCmd, []},[]}};
+ {Line, Ls2} -> % found. Complete the output edlin couldn't have done.
+ Lines = string:split(string:to_graphemes(Line), "\n", all),
+ send_drv(Drv, delete_line),
+ send_drv(Drv, {insert_chars, unicode, unicode:characters_to_binary(Prompt++Cmd)}),
+ send_drv(Drv, {put_expand, unicode, unicode:characters_to_binary(" "++lists:join("\n ",Lines)), 7}),
+ {Ls2, Lines, {[],{RevCmd, []},[]}}
+ end,
+ Cont = {line,Prompt,NewStack,{search, none}},
+ {What, {Cont, State#get_line_edlin_state{ history = Ls, search = RevCmd, search_result = SearchResult }}}
end;
-get_line1({What,Cont0,Rs}, Drv, Shell, Ls, Encoding) ->
+get_line_edlin({What,Cont0,Rs}, Drv, State) ->
send_drv_reqs(Drv, Rs),
- more_data(What, Cont0, Drv, Shell, Ls, Encoding).
-
-more_data(What, Cont0, Drv, Shell, Ls, Encoding) ->
- receive
- {Drv, activate} ->
- send_drv_reqs(Drv, edlin:redraw_line(Cont0)),
- more_data(What, Cont0, Drv, Shell, Ls, Encoding);
- {Drv,{data,Cs}} ->
- Res = edlin:edit_line(cast(Cs, list), Cont0),
- get_line1(Res,
- Drv, Shell, Ls, Encoding);
- {Drv,eof} ->
- get_line1(edlin:edit_line(eof, Cont0), Drv, Shell, Ls, Encoding);
- {io_request,From,ReplyAs,Req} when is_pid(From) ->
- {more_chars,Cont,_More} = edlin:edit_line([], Cont0),
- send_drv_reqs(Drv, edlin:erase_line()),
- io_request(Req, From, ReplyAs, Drv, Shell, []), %WRONG!!!
- send_drv_reqs(Drv, edlin:redraw_line(Cont)),
- get_line1({more_chars,Cont,[]}, Drv, Shell, Ls, Encoding);
- {reply,{From,ReplyAs},Reply} ->
- %% We take care of replies from puts here as well
- io_reply(From, ReplyAs, Reply),
- more_data(What, Cont0, Drv, Shell, Ls, Encoding);
- {'EXIT',Drv,interrupt} ->
- interrupted;
- {'EXIT',Drv,_} ->
- terminated;
- {'EXIT',Shell,R} ->
- exit(R)
- after
- get_line_timeout(What)->
- get_line1(edlin:edit_line([], Cont0), Drv, Shell, Ls, Encoding)
- end.
-
-get_line_echo_off(Chars, ToEnc, Pbs, Drv, Shell) ->
- send_drv_reqs(Drv, [{put_chars, unicode,Pbs}]),
- case get_line_echo_off1(edit_line(Chars,[]), Drv, Shell) of
- {done, Line, _Rest} = Res when ToEnc =:= latin1 ->
- case check_encoding(Line, ToEnc) of
- false ->
- {no_translation, unicode, ToEnc};
- true ->
- Res
- end;
- Res ->
- Res
- end.
-
-get_line_echo_off1({Chars,[],Rs}, Drv, Shell) ->
- case get(echo) of
- true -> send_drv_reqs(Drv, Rs);
- false -> skip
- end,
- receive
- {Drv,{data,Cs}} ->
- get_line_echo_off1(edit_line(cast(Cs, list), Chars), Drv, Shell);
- {Drv,eof} ->
- get_line_echo_off1(edit_line(eof, Chars), Drv, Shell);
- {io_request,From,ReplyAs,Req} when is_pid(From) ->
- io_request(Req, From, ReplyAs, Drv, Shell, []),
- get_line_echo_off1({Chars,[],[]}, Drv, Shell);
- {reply,{From,ReplyAs},Reply} when From =/= undefined ->
- %% We take care of replies from puts here as well
- io_reply(From, ReplyAs, Reply),
- get_line_echo_off1({Chars,[],[]},Drv, Shell);
- {'EXIT',Drv,interrupt} ->
- interrupted;
- {'EXIT',Drv,_} ->
- terminated;
- {'EXIT',Shell,R} ->
- exit(R)
- end;
-get_line_echo_off1(eof, _Drv, _Shell) ->
- {done,eof,eof};
-get_line_echo_off1({Chars,Rest,Rs}, Drv, _Shell) ->
- case get(echo) of
- true -> send_drv_reqs(Drv, Rs);
- false -> skip
- end,
- {done,lists:reverse(Chars),case Rest of done -> []; _ -> Rest end}.
-get_chars_echo_off(Pbs, Drv, Shell) ->
- send_drv_reqs(Drv, [{insert_chars, unicode,Pbs}]),
- get_chars_echo_off1(Drv, Shell).
-
-get_chars_echo_off1(Drv, Shell) ->
- receive
- {Drv, {data, Cs}} ->
- cast(Cs, list);
- {Drv, eof} ->
- eof;
- {io_request,From,ReplyAs,Req} when is_pid(From) ->
- io_request(Req, From, ReplyAs, Drv, Shell, []),
- get_chars_echo_off1(Drv, Shell);
- {reply,{From,ReplyAs},Reply} when From =/= undefined ->
- %% We take care of replies from puts here as well
- io_reply(From, ReplyAs, Reply),
- get_chars_echo_off1(Drv, Shell);
- {'EXIT',Drv,interrupt} ->
- interrupted;
- {'EXIT',Drv,_} ->
- terminated;
- {'EXIT',Shell,R} ->
- exit(R)
- end.
+ {What, {Cont0, State}}.
format_expression(Cont, Drv) ->
FormatingCommand = application:get_env(stdlib, format_shell_func, default),
@@ -983,11 +1042,11 @@ format_expression1(Buffer, FormatingCommand) ->
%% Write the current expression to a file, format it with a formatting tool
%% provided by the user and read the file back
MkTemp = case os:type() of
- {win32, _} ->
- os:cmd("powershell \"write-host (& New-TemporaryFile | Select-Object -ExpandProperty FullName)\"");
- {unix,_} ->
- os:cmd("mktemp")
- end,
+ {win32, _} ->
+ os:cmd("powershell \"write-host (& New-TemporaryFile | Select-Object -ExpandProperty FullName)\"");
+ {unix,_} ->
+ os:cmd("mktemp")
+ end,
TmpFile = string:chomp(MkTemp) ++ ".erl",
_ = file:write_file(TmpFile, unicode:characters_to_binary(Buffer, unicode)),
FormattingCommand1 = string:replace(FormatingCommand, "${file}", TmpFile),
@@ -1001,20 +1060,57 @@ format_expression1(Buffer, FormatingCommand) ->
end,
string:chomp(Unicode).
-%% Edit line is used in echo=false mode which has two users
-%% Either we are running in "oldshell" or we run using "noshell".
-%%
-%% For "oldshell" we need to take care of certain special characters
-%% that can be entered, but for "noshell" we don't want to do any of
-%% that.
-edit_line(Input, State) ->
- case get(noshell) of
- false ->
- edit_line(Input, State, []);
- true ->
- edit_line_raw(Input, State, [])
+get_line_dumb(Buf, Pbs, undefined, ToEnc, Data) ->
+ send_drv_reqs(Data#state.driver, [{put_chars, unicode, Pbs}]),
+ get_line_dumb(Buf, Pbs, [], ToEnc, Data);
+get_line_dumb(Buf, _Pbs, Cont, ToEnc, Data = #state{ driver = Drv }) ->
+
+ EditLineRes =
+ if
+ Data#state.shell =:= noshell -> edit_line_noshell(cast(Buf, list), Cont, []);
+ true -> edit_line_dumb(cast(Buf, list), Cont, [])
+ end,
+
+ case EditLineRes of
+ {more, NewCont, Rs} ->
+ [send_drv_reqs(Drv, Rs) || Data#state.echo],
+ {more_chars, NewCont};
+ eof ->
+ {done, eof, eof};
+ {done, Enil, Rest, Rs} ->
+ [send_drv_reqs(Drv, Rs) || Data#state.echo],
+
+ Line = lists:reverse(Enil),
+ case check_encoding(Line, ToEnc) of
+ false ->
+ {no_translation, unicode, ToEnc};
+ true ->
+ {done, Line, Rest}
+ end
end.
+get_chars_dumb(Buf, Pbs, undefined, ToEnc, Data) ->
+ send_drv_reqs(Data#state.driver, [{put_chars, unicode, Pbs}]),
+ get_chars_dumb(Buf, Pbs, [], ToEnc, Data);
+get_chars_dumb(Buf, _Pbs, _Cont, ToEnc, Data = #state{ driver = Drv }) ->
+
+ case cast(Buf, list) of
+ [] ->
+ {more_chars, []};
+ eof ->
+ {done, eof, eof};
+ Chars ->
+ [send_drv_reqs(Drv, [{put_chars, unicode, Chars}]) || Data#state.echo],
+
+ case check_encoding(Chars, ToEnc) of
+ false ->
+ {no_translation, unicode, ToEnc};
+ true ->
+ {done, Chars, []}
+ end
+ end.
+
+%% This is used by oldshell to get a basic line editor
%% We support line editing for the ICANON mode except the following
%% line editing characters, which already has another meaning in
%% echo-on mode (See Advanced Programming in the Unix Environment, 2nd ed,
@@ -1024,42 +1120,38 @@ edit_line(Input, State) ->
%% - ^d in posix/icanon mode: eof, delete-forward in edlin
%% - ^r in posix/icanon mode: reprint (silly in echo-off mode :-))
%% - ^w in posix/icanon mode: word-erase (produces a beep in edlin)
-edit_line(eof, [], _) ->
+edit_line_dumb(eof, [], _) ->
eof;
-edit_line(eof, Chars, Rs) ->
- {Chars,eof, lists:reverse(Rs)};
-edit_line([],Chars, Rs) ->
- {Chars,[],lists:reverse(Rs)};
-edit_line([$\r,$\n|Cs],Chars, Rs) ->
- {[$\n | Chars], remainder_after_nl(Cs), lists:reverse([{put_chars, unicode, "\n"}|Rs])};
-edit_line([NL|Cs],Chars, Rs) when NL =:= $\r; NL =:= $\n ->
- {[$\n | Chars], remainder_after_nl(Cs), lists:reverse([{put_chars, unicode, "\n"}|Rs])};
-edit_line([Erase|Cs],[], Rs) when Erase =:= $\177; Erase =:= $\^H ->
- edit_line(Cs,[], Rs);
-edit_line([Erase|Cs],[_|Chars], Rs) when Erase =:= $\177; Erase =:= $\^H ->
- edit_line(Cs,Chars, [{delete_chars, -1}|Rs]);
-edit_line([CtrlChar|Cs],Chars, Rs) when CtrlChar < 32 ->
- edit_line(Cs,Chars,Rs);
-edit_line([Char|Cs],Chars, Rs) ->
- edit_line(Cs,[Char|Chars], [{put_chars, unicode, [Char]}|Rs]).
-
-edit_line_raw(eof, [], _) ->
+edit_line_dumb(eof, Chars, Rs) ->
+ {done, Chars, eof, lists:reverse(Rs)};
+edit_line_dumb([], Chars, Rs) ->
+ {more, Chars, lists:reverse(Rs)};
+edit_line_dumb([$\r,$\n|Cs],Chars, Rs) ->
+ {done, [$\n | Chars], Cs, lists:reverse([{put_chars, unicode, "\n"}|Rs])};
+edit_line_dumb([NL|Cs],Chars, Rs) when NL =:= $\r; NL =:= $\n ->
+ {done, [$\n | Chars], Cs, lists:reverse([{put_chars, unicode, "\n"}|Rs])};
+edit_line_dumb([Erase|Cs],[], Rs) when Erase =:= $\177; Erase =:= $\^H ->
+ edit_line_dumb(Cs,[], Rs);
+edit_line_dumb([Erase|Cs],[_|Chars], Rs) when Erase =:= $\177; Erase =:= $\^H ->
+ edit_line_dumb(Cs,Chars, [{delete_chars, -1}|Rs]);
+edit_line_dumb([CtrlChar|Cs],Chars, Rs) when CtrlChar < 32 ->
+ edit_line_dumb(Cs,Chars,Rs);
+edit_line_dumb([Char|Cs],Chars, Rs) ->
+ edit_line_dumb(Cs,[Char|Chars], [{put_chars, unicode, [Char]}|Rs]).
+
+%% This is used by noshell to get just get everything until the next \n
+edit_line_noshell(eof, [], _) ->
eof;
-edit_line_raw(eof, Chars, Rs) ->
- {Chars,eof, lists:reverse(Rs)};
-edit_line_raw([],Chars, Rs) ->
- {Chars,[],lists:reverse(Rs)};
-edit_line_raw([NL|Cs],Chars, Rs) when NL =:= $\n ->
- {[$\n | Chars], remainder_after_nl(Cs), lists:reverse([{put_chars, unicode, "\n"}|Rs])};
-edit_line_raw([Char|Cs],Chars, Rs) ->
- edit_line_raw(Cs,[Char|Chars], [{put_chars, unicode, [Char]}|Rs]).
-
-remainder_after_nl("") -> done;
-remainder_after_nl(Cs) -> Cs.
-
-get_line_timeout(blink) -> 1000;
-get_line_timeout(more_chars) -> infinity.
-
+edit_line_noshell(eof, Chars, Rs) ->
+ {done, Chars, eof, lists:reverse(Rs)};
+edit_line_noshell([],Chars, Rs) ->
+ {more, Chars, lists:reverse(Rs)};
+edit_line_noshell([NL|Cs],Chars, Rs) when NL =:= $\n ->
+ {done, [$\n | Chars], Cs, lists:reverse([{put_chars, unicode, "\n"}|Rs])};
+edit_line_noshell([Char|Cs],Chars, Rs) ->
+ edit_line_noshell(Cs, [Char|Chars], [{put_chars, unicode, [Char]}|Rs]).
+
+%% Handling of the line history stack
new_stack(Ls) -> {stack,Ls,{},[]}.
up_stack({stack,[L|U],{},D}) ->
@@ -1117,9 +1209,9 @@ pad_stack({stack, U, L, D}) ->
{stack, U, L, D++["\n"]}.
save_line_buffer("\n", Lines) ->
- save_line_buffer(Lines);
+ Lines;
save_line_buffer(Line, [Line|_Lines]=Lines) ->
- save_line_buffer(Lines);
+ Lines;
save_line_buffer(Line, Lines) ->
try
group_history:add(Line)
@@ -1127,10 +1219,7 @@ save_line_buffer(Line, Lines) ->
?LOG_ERROR(#{ msg => "Failed to write to shell history",
error => {E, R, ST} })
end,
- save_line_buffer([Line|Lines]).
-
-save_line_buffer(Lines) ->
- put(line_buffer, Lines).
+ [Line|Lines].
search_up_stack(Stack, Substr) ->
case up_stack(Stack) of
@@ -1152,50 +1241,6 @@ search_down_stack(Stack, Substr) ->
end
end.
-
-%% This is get_line without line editing (except for backspace) and
-%% without echo.
-get_password_line(Chars, Drv, Shell) ->
- get_password1(edit_password(Chars,[]),Drv,Shell).
-
-get_password1({Chars,[]}, Drv, Shell) ->
- receive
- {Drv,{data,Cs}} ->
- get_password1(edit_password(cast(Cs,list),Chars),Drv,Shell);
- {io_request,From,ReplyAs,Req} when is_pid(From) ->
- io_request(Req, From, ReplyAs, Drv, Shell, []), %WRONG!!!
- %% I guess the reason the above line is wrong is that Buf is
- %% set to []. But do we expect anything but plain output?
-
- get_password1({Chars, []}, Drv, Shell);
- {reply,{From,ReplyAs},Reply} ->
- %% We take care of replies from puts here as well
- io_reply(From, ReplyAs, Reply),
- get_password1({Chars, []}, Drv, Shell);
- {'EXIT',Drv,interrupt} ->
- interrupted;
- {'EXIT',Drv,_} ->
- terminated;
- {'EXIT',Shell,R} ->
- exit(R)
- end;
-get_password1({Chars,Rest},Drv,_Shell) ->
- send_drv_reqs(Drv,[{insert_chars, unicode, "\n"}]),
- {done,lists:reverse(Chars),case Rest of done -> []; _ -> Rest end}.
-
-edit_password([],Chars) ->
- {Chars,[]};
-edit_password([$\r],Chars) ->
- {Chars,done};
-edit_password([$\r|Cs],Chars) ->
- {Chars,Cs};
-edit_password([$\177|Cs],[]) -> %% Being able to erase characters is
- edit_password(Cs,[]); %% the least we should offer, but
-edit_password([$\177|Cs],[_|Chars]) ->%% is backspace enough?
- edit_password(Cs,Chars);
-edit_password([Char|Cs],Chars) ->
- edit_password(Cs,[Char|Chars]).
-
%% prompt_bytes(Prompt, Encoding)
%% Return a flat list of characters for the Prompt.
prompt_bytes(Prompt, Encoding) ->
@@ -1226,8 +1271,6 @@ append(L, A, _) when is_list(L) ->
append(B, L, FromEnc) ->
append(unicode:characters_to_list(B, FromEnc), L, FromEnc).
-check_encoding(eof, _) ->
- true;
check_encoding(ListOrBinary, unicode) when is_list(ListOrBinary); is_binary(ListOrBinary) ->
true;
check_encoding(List, latin1) when is_list(List) ->
diff --git a/lib/kernel/src/user_drv.erl b/lib/kernel/src/user_drv.erl
index 067e97e0f4..d6666acd69 100644
--- a/lib/kernel/src/user_drv.erl
+++ b/lib/kernel/src/user_drv.erl
@@ -305,7 +305,7 @@ init_remote_shell(State, Node, {M, F, A}) ->
end,
Group = group:start(self(), RShell,
- [{echo,State#state.shell_started =:= new}] ++
+ [{dumb, State#state.shell_started =/= new}] ++
group_opts(RemoteNode)),
Gr = gr_add_cur(State#state.groups, Group, RShell),
@@ -329,7 +329,7 @@ init_local_shell(State, InitialShell) ->
Gr = gr_add_cur(State#state.groups,
group:start(self(), InitialShell,
- group_opts() ++ [{echo,State#state.shell_started =:= new}]),
+ group_opts() ++ [{dumb,State#state.shell_started =/= new}]),
InitialShell),
init_shell(State#state{ groups = Gr }, [Slogan,$\n]).
@@ -351,10 +351,7 @@ init_shell(State, Slogan) ->
start_user() ->
case whereis(user) of
undefined ->
- User = group:start(self(), {}, [{echo,false},
- {noshell,true}]),
- register(user, User),
- User;
+ group:start(self(), noshell, [{name, user}]);
User ->
User
end.
@@ -625,7 +622,7 @@ switch_loop(internal, line, State) ->
switch_loop(internal, {line, Line}, State) ->
case erl_scan:string(Line) of
{ok, Tokens, _} ->
- case switch_cmd(Tokens, State#state.groups) of
+ case switch_cmd(Tokens, State#state.groups, State#state.shell_started =/= new) of
{ok, Groups} ->
Curr = gr_cur_pid(Groups),
put(current_group, Curr),
@@ -692,24 +689,24 @@ switch_loop(timeout, _, {_Cont, State}) ->
switch_loop(info, _Unknown, _State) ->
{keep_state_and_data, postpone}.
-switch_cmd([{atom,_,Key},{Type,_,Value}], Gr)
+switch_cmd([{atom,_,Key},{Type,_,Value}], Gr, Dumb)
when Type =:= atom; Type =:= integer ->
- switch_cmd({Key, Value}, Gr);
-switch_cmd([{atom,_,Key},{atom,_,V1},{atom,_,V2}], Gr) ->
- switch_cmd({Key, V1, V2}, Gr);
-switch_cmd([{atom,_,Key}], Gr) ->
- switch_cmd(Key, Gr);
-switch_cmd([{'?',_}], Gr) ->
- switch_cmd(h, Gr);
-
-switch_cmd(Cmd, Gr) when Cmd =:= c; Cmd =:= i; Cmd =:= k ->
- switch_cmd({Cmd, gr_cur_index(Gr)}, Gr);
-switch_cmd({c, I}, Gr0) ->
+ switch_cmd({Key, Value}, Gr, Dumb);
+switch_cmd([{atom,_,Key},{atom,_,V1},{atom,_,V2}], Gr, Dumb) ->
+ switch_cmd({Key, V1, V2}, Gr, Dumb);
+switch_cmd([{atom,_,Key}], Gr, Dumb) ->
+ switch_cmd(Key, Gr, Dumb);
+switch_cmd([{'?',_}], Gr, Dumb) ->
+ switch_cmd(h, Gr, Dumb);
+
+switch_cmd(Cmd, Gr, Dumb) when Cmd =:= c; Cmd =:= i; Cmd =:= k ->
+ switch_cmd({Cmd, gr_cur_index(Gr)}, Gr, Dumb);
+switch_cmd({c, I}, Gr0, _Dumb) ->
case gr_set_cur(Gr0, I) of
{ok,Gr} -> {ok, Gr};
undefined -> unknown_group()
end;
-switch_cmd({i, I}, Gr) ->
+switch_cmd({i, I}, Gr, _Dumb) ->
case gr_get_num(Gr, I) of
{pid,Pid} ->
exit(Pid, interrupt),
@@ -717,7 +714,7 @@ switch_cmd({i, I}, Gr) ->
undefined ->
unknown_group()
end;
-switch_cmd({k, I}, Gr) ->
+switch_cmd({k, I}, Gr, _Dumb) ->
case gr_get_num(Gr, I) of
{pid,Pid} ->
exit(Pid, die),
@@ -734,15 +731,15 @@ switch_cmd({k, I}, Gr) ->
undefined ->
unknown_group()
end;
-switch_cmd(j, Gr) ->
+switch_cmd(j, Gr, _Dumb) ->
{retry, gr_list(Gr)};
-switch_cmd({s, Shell}, Gr0) when is_atom(Shell) ->
- Pid = group:start(self(), {Shell,start,[]}),
+switch_cmd({s, Shell}, Gr0, Dumb) when is_atom(Shell) ->
+ Pid = group:start(self(), {Shell,start,[]}, [{dumb, Dumb} | group_opts()]),
Gr = gr_add_cur(Gr0, Pid, {Shell,start,[]}),
{retry, [], Gr};
-switch_cmd(s, Gr) ->
- switch_cmd({s, shell}, Gr);
-switch_cmd(r, Gr0) ->
+switch_cmd(s, Gr, Dumb) ->
+ switch_cmd({s, shell}, Gr, Dumb);
+switch_cmd(r, Gr0, _Dumb) ->
case is_alive() of
true ->
Node = pool:get_node(),
@@ -752,30 +749,35 @@ switch_cmd(r, Gr0) ->
false ->
{retry, [{put_chars,unicode,<<"Node is not alive\n">>}]}
end;
-switch_cmd({r, Node}, Gr) when is_atom(Node)->
- switch_cmd({r, Node, shell}, Gr);
-switch_cmd({r,Node,Shell}, Gr0) when is_atom(Node), is_atom(Shell) ->
+switch_cmd({r, Node}, Gr, Dumb) when is_atom(Node)->
+ switch_cmd({r, Node, shell}, Gr, Dumb);
+switch_cmd({r,Node,Shell}, Gr0, Dumb) when is_atom(Node), is_atom(Shell) ->
case is_alive() of
true ->
- Pid = group:start(self(), {Node,Shell,start,[]}, group_opts(Node)),
- Gr = gr_add_cur(Gr0, Pid, {Node,Shell,start,[]}),
- {retry, [], Gr};
+ case net_kernel:connect_node(Node) of
+ true ->
+ Pid = group:start(self(), {Node,Shell,start,[]}, [{dumb, Dumb} | group_opts(Node)]),
+ Gr = gr_add_cur(Gr0, Pid, {Node,Shell,start,[]}),
+ {retry, [], Gr};
+ false ->
+ {retry, [{put_chars,unicode,<<"Could not connect to node\n">>}]}
+ end;
false ->
{retry, [{put_chars,unicode,"Node is not alive\n"}]}
end;
-switch_cmd(q, _Gr) ->
+switch_cmd(q, _Gr, _Dumb) ->
case erlang:system_info(break_ignored) of
true -> % noop
{retry, [{put_chars,unicode,<<"Unknown command\n">>}]};
false ->
halt()
end;
-switch_cmd(h, _Gr) ->
+switch_cmd(h, _Gr, _Dumb) ->
{retry, list_commands()};
-switch_cmd([], _Gr) ->
+switch_cmd([], _Gr, _Dumb) ->
{retry,[]};
-switch_cmd(_Ts, _Gr) ->
+switch_cmd(_Ts, _Gr, _Dumb) ->
{retry, [{put_chars,unicode,<<"Unknown command\n">>}]}.
unknown_group() ->
diff --git a/lib/kernel/test/interactive_shell_SUITE.erl b/lib/kernel/test/interactive_shell_SUITE.erl
index 8a8399a26e..f48f2d397b 100644
--- a/lib/kernel/test/interactive_shell_SUITE.erl
+++ b/lib/kernel/test/interactive_shell_SUITE.erl
@@ -1339,7 +1339,7 @@ shell_get_password(_Config) ->
rtnode:run(
[{putline,"io:get_password()."},
{putline,"secret\r"},
- {expect, "\r\n\r\n\"secret\""}]),
+ {expect, "\r\n\"secret\""}]),
%% io:get_password only works when run in "newshell"
rtnode:run(
diff --git a/lib/ssh/src/ssh_cli.erl b/lib/ssh/src/ssh_cli.erl
index 5eb3e41980..e2c1f74017 100644
--- a/lib/ssh/src/ssh_cli.erl
+++ b/lib/ssh/src/ssh_cli.erl
@@ -740,7 +740,8 @@ start_shell(ConnectionHandler, State) ->
Shell
end,
State#state{group = group:start(self(), ShellSpawner,
- [{dumb, get_dumb(State#state.pty)},{expand_below, false},
+ [{dumb, get_dumb(State#state.pty)},
+ {expand_below, false},
{echo, get_echo(State#state.pty)}]),
buf = empty_buf()}.
@@ -763,7 +764,7 @@ start_exec_shell(ConnectionHandler, Cmd, State) ->
{M, F, A++[Cmd]}
end,
State#state{group = group:start(self(), ExecShellSpawner, [{expand_below, false},
- {echo,false}]),
+ {dumb, true}]),
buf = empty_buf()}.
%%--------------------------------------------------------------------
@@ -848,7 +849,7 @@ exec_in_self_group(ConnectionHandler, ChannelId, WantReply, State, Fun) ->
end)
end,
{ok, State#state{group = group:start(self(), Exec, [{expand_below, false},
- {echo,false}]),
+ {dumb, true}]),
buf = empty_buf()}}.
diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl
index 0b300088cb..543496c34c 100644
--- a/lib/stdlib/src/io_lib.erl
+++ b/lib/stdlib/src/io_lib.erl
@@ -85,9 +85,9 @@ used for flattening deep lists.
deep_char_list/1, deep_latin1_char_list/1,
printable_list/1, printable_latin1_list/1, printable_unicode_list/1]).
-%% Utilities for collecting characters.
+%% Utilities for collecting characters mostly used by group
-export([collect_chars/3, collect_chars/4,
- collect_line/3, collect_line/4,
+ collect_line/3, collect_line/4, collect_line_no_eol/4,
get_until/3, get_until/4]).
%% The following functions were used by Yecc's include-file.
@@ -1144,6 +1144,16 @@ collect_chars_list(Stack,N, [H|T]) ->
collect_line(Tag, Data, Any) ->
collect_line(Tag, Data, latin1, Any).
+%% A special variant of collect line that trims the last newline
+%% used by io:get_password/0,1
+-doc false.
+collect_line_no_eol(Tag, Data, Encoding, Any) ->
+ case collect_line(Tag, Data, Encoding, Any) of
+ {stop, Line, Rest} when Line =/= eof ->
+ {stop, string:trim(Line), Rest};
+ Else -> Else
+ end.
+
%% Now we are aware of encoding...
-doc false.
collect_line(start, Data, Encoding, _) when is_binary(Data) ->
--
2.43.0