Skip to content

Commit

Permalink
Remsh from or to an old node expand compability
Browse files Browse the repository at this point in the history
  • Loading branch information
frazze-jobb committed Aug 22, 2022
1 parent 7dc02f0 commit 2e31321
Show file tree
Hide file tree
Showing 13 changed files with 1,449 additions and 1,338 deletions.
19 changes: 5 additions & 14 deletions lib/common_test/src/test_server_node.erl
Expand Up @@ -490,20 +490,11 @@ find_release_path([Path|T], Rel) ->
false ->
find_release_path(T, Rel);
ErlExec ->
Pattern = filename:join([Path,"..","releases","*","OTP_VERSION"]),
case filelib:wildcard(Pattern) of
[VersionFile] ->
{ok, VsnBin} = file:read_file(VersionFile),
[MajorVsn|_] = string:lexemes(VsnBin, "."),
case unicode:characters_to_list(MajorVsn) of
Rel ->
ErlExec;
_Else ->
find_release_path(T, Rel)
end;
_Else ->
find_release_path(T, Rel)
end
Release = os:cmd(ErlExec ++ " -noinput -eval 'io:format(\"~ts\", [erlang:system_info(otp_release)])' -s init stop"),
case Release =:= Rel of
true -> ErlExec;
false -> find_release_path(T, Rel)
end
end;
find_release_path([], _) ->
none.
Expand Down
20 changes: 10 additions & 10 deletions lib/kernel/src/group.erl
Expand Up @@ -39,9 +39,9 @@ server(Drv, Shell, Options) ->
put(tab_count, 0),
put(expand_fun,
proplists:get_value(expand_fun, Options,
fun(B) -> edlin_expand:expand(B) end)),
fun edlin_expand:expand/2)),
put(echo, proplists:get_value(echo, Options, true)),

start_shell(Shell),
server_loop(Drv, get(shell), []).

Expand Down Expand Up @@ -197,12 +197,12 @@ io_request(Req, From, ReplyAs, Drv, Shell, Buf0) ->
end.


%% Put_chars, unicode is the normal message, characters are always in
%% 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
%% 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) ->
%% io_request({put_chars,unicode,Binary}, Drv, Buf) when is_binary(Binary) ->
%% send_drv(Drv, {put_chars,Binary}),
%% {ok,ok,Buf};
%%
Expand Down Expand Up @@ -361,7 +361,7 @@ expand_encoding([H|T]) ->
setopts(Opts0,Drv,Buf) ->
Opts = proplists:unfold(
proplists:substitute_negations(
[{list,binary}],
[{list,binary}],
expand_encoding(Opts0))),
case check_valid_opts(Opts) of
true ->
Expand Down Expand Up @@ -431,7 +431,7 @@ getopts(Drv,Buf) ->
_ -> latin1
end},
{ok,[Exp,Echo,Bin,Uni],Buf}.


%% get_chars_*(Prompt, Module, Function, XtraArgument, Drv, Buffer)
%% Gets characters from the input Drv until as the applied function
Expand Down Expand Up @@ -597,7 +597,7 @@ get_line1({undefined,{_A, Mode, Char}, _Cs, Cont, Rs}, Drv, Shell, Ls0, Encoding
put(expression_buffer, []),
send_drv(Drv, {open_editor, list_to_binary(Buffer)}),
receive
{Drv, {editor_data, Cs}} ->
{Drv, {editor_data, Cs}} ->
send_drv_reqs(Drv, edlin:erase_line(Cont)),
{more_chars,NewCont,NewRs} = edlin:start(edlin:prompt(Cont)),
send_drv_reqs(Drv, NewRs),
Expand Down Expand Up @@ -664,7 +664,7 @@ get_line1({expand, Before, Cs0, Cont,Rs}, Drv, Shell, Ls0, Encoding) ->
PrevInput = string:join(string:tokens(get(expression_buffer)," \t\n\r"), " "),
send_drv_reqs(Drv, Rs),
ExpandFun = get(expand_fun),
{Found, CompleteChars, Matches} = ExpandFun(Before++lists:reverse(PrevInput)),
{Found, CompleteChars, Matches} = ExpandFun(Before++lists:reverse(PrevInput), []),
case Found of
no -> send_drv(Drv, beep);
_ -> ok
Expand Down Expand Up @@ -849,7 +849,7 @@ edit_line([Char|Cs],Chars) ->

remainder_after_nl("") -> done;
remainder_after_nl(Cs) -> Cs.



get_line_timeout(blink) -> 1000;
Expand Down
13 changes: 9 additions & 4 deletions lib/kernel/src/user_drv.erl
Expand Up @@ -167,7 +167,12 @@ append_hostname(Node, LocalNode) ->
end.

rem_sh_opts(Node) ->
[{expand_fun,fun(B)-> rpc:call(Node,edlin_expand,expand,[B]) end}].
VersionString = erpc:call(Node, erlang, system_info, [otp_release]),
Version = list_to_integer(VersionString),
case Version > 25 of
true -> [{expand_fun,fun(B, Opts)-> erpc:call(Node,edlin_expand,expand,[B, Opts]) end}];
false -> [{expand_fun,fun(B, _)-> erpc:call(Node,edlin_expand,expand,[B]) end}]
end.

%% start_user()
%% Start a group leader process and register it as 'user', unless,
Expand Down Expand Up @@ -445,20 +450,20 @@ switch_cmd({ok,[{atom,_,r}],_}, Iport, Oport, Gr0) ->
case is_alive() of
true ->
Node = pool:get_node(),
Pid = group:start(self(), {Node,shell,start,[]}),
Pid = group:start(self(), {Node,shell,start,[]}, rem_sh_opts(Node)),
Gr = gr_add_cur(Gr0, Pid, {Node,shell,start,[]}),
switch_loop(Iport, Oport, Gr);
false ->
io_request({put_chars,unicode,"Not alive\n"}, Iport, Oport),
switch_loop(Iport, Oport, Gr0)
end;
switch_cmd({ok,[{atom,_,r},{atom,_,Node}],_}, Iport, Oport, Gr0) ->
Pid = group:start(self(), {Node,shell,start,[]}),
Pid = group:start(self(), {Node,shell,start,[]}, rem_sh_opts(Node)),
Gr = gr_add_cur(Gr0, Pid, {Node,shell,start,[]}),
switch_loop(Iport, Oport, Gr);
switch_cmd({ok,[{atom,_,r},{atom,_,Node},{atom,_,Shell}],_},
Iport, Oport, Gr0) ->
Pid = group:start(self(), {Node,Shell,start,[]}),
Pid = group:start(self(), {Node,Shell,start,[]}, rem_sh_opts(Node)),
Gr = gr_add_cur(Gr0, Pid, {Node,Shell,start,[]}),
switch_loop(Iport, Oport, Gr);
switch_cmd({ok,[{atom,_,q}],_}, Iport, Oport, Gr) ->
Expand Down

0 comments on commit 2e31321

Please sign in to comment.