File 2604-kernel-Refactor-out-rtnode-code-to-seperate-module.patch of Package erlang
From d304a41f1e5b1a0f0ba78142bec1fcd5973b0fd3 Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Thu, 30 Jun 2022 22:33:43 +0200
Subject: [PATCH 4/5] kernel: Refactor out rtnode code to seperate module
rtnode is used for testing in two suites, so instead of
duplicating the code we create a module that both can use.
---
lib/kernel/test/Makefile | 1 +
lib/kernel/test/interactive_shell_SUITE.erl | 1199 ++++++-------------
lib/kernel/test/rtnode.erl | 538 +++++++++
lib/stdlib/test/Makefile | 6 +-
lib/stdlib/test/io_proto_SUITE.erl | 856 +++----------
5 files changed, 1094 insertions(+), 1506 deletions(-)
create mode 100644 lib/kernel/test/rtnode.erl
diff --git a/lib/kernel/test/Makefile b/lib/kernel/test/Makefile
index 130e626b56..413349d98a 100644
--- a/lib/kernel/test/Makefile
+++ b/lib/kernel/test/Makefile
@@ -107,6 +107,7 @@ MODULES= \
net_SUITE \
os_SUITE \
pg_SUITE \
+ rtnode \
seq_trace_SUITE \
$(SOCKET_MODULES) \
wrap_log_reader_SUITE \
diff --git a/lib/kernel/test/interactive_shell_SUITE.erl b/lib/kernel/test/interactive_shell_SUITE.erl
index f5097b83aa..d303d42eda 100644
--- a/lib/kernel/test/interactive_shell_SUITE.erl
+++ b/lib/kernel/test/interactive_shell_SUITE.erl
@@ -34,8 +34,6 @@
get_columns_and_rows_escript/1,
remsh_basic/1, remsh_longnames/1, remsh_no_epmd/1]).
-%% For spawn
--export([toerl_server/4]).
%% Exports for custom shell history module
-export([load/0, add/1]).
@@ -71,13 +69,13 @@ groups() ->
].
init_per_suite(Config) ->
- case get_progs() of
- {error, Error} ->
- {skip, Error};
- _ ->
- Term = os:getenv("TERM", "dumb"),
- os:putenv("TERM", "vt100"),
- DefShell = get_default_shell(),
+ Term = os:getenv("TERM", "dumb"),
+ os:putenv("TERM", "vt100"),
+ case rtnode:get_default_shell() of
+ noshell ->
+ os:putenv("TERM",Term),
+ {skip, "No run_erl"};
+ DefShell ->
[{default_shell,DefShell},{term,Term}|Config]
end.
@@ -99,7 +97,7 @@ init_per_group(shell_history, Config) ->
init_per_group(sh_custom, Config) ->
%% Ensure that ERL_AFLAGS will not override the value of the shell_history variable.
{ok, Peer, Node} = ?CT_PEER(["-noshell","-kernel","shell_history","not_overridden"]),
- try erpc:call(Node, application, get_env, [kernel, shell_history], timeout(normal)) of
+ try erpc:call(Node, application, get_env, [kernel, shell_history], rtnode:timeout(normal)) of
{ok, not_overridden} ->
Config;
_ ->
@@ -153,7 +151,7 @@ run_unbuffer_escript(Rows, Columns, EScript, NoTermStdIn, NoTermStdOut) ->
{true, true} -> io_lib:format(" > ~s < ~s ; cat ~s", [TmpFile, TmpFile, TmpFile])
end,
Command = io_lib:format("unbuffer -p bash -c \"stty rows ~p; stty columns ~p; escript ~s ~s\"",
- [Rows, Columns, EScript, CommandModifier]),
+ [Rows, Columns, EScript, CommandModifier]),
%% io:format("Command: ~s ~n", [Command]),
Out = os:cmd(Command),
%% io:format("Out: ~p ~n", [Out]),
@@ -201,50 +199,54 @@ get_columns_and_rows(Config) when is_list(Config) ->
ok.
test_columns_and_rows(old, Args) ->
- rtnode([{putline, ""},
- {putline, "2."},
- {expect, "2\r\n"},
- {putline, "io:columns()."},
- {expect, "{error,enotsup}\r\n"},
- {putline, "io:rows()."},
- {expect, "{error,enotsup}\r\n"}
- ], [], [], Args),
-
- rtnode([{putline, ""},
- {putline, "2."},
- {expect, "2\r\n"},
- {putline, "io:columns()."},
- {expect, "{ok,90}\r\n"},
- {putline,"io:rows()."},
- {expect, "{ok,40}\r\n"}],
- [],
- "stty rows 40; stty columns 90; ",
- Args);
+ rtnode:run(
+ [{putline, ""},
+ {putline, "2."},
+ {expect, "2\r\n"},
+ {putline, "io:columns()."},
+ {expect, "{error,enotsup}\r\n"},
+ {putline, "io:rows()."},
+ {expect, "{error,enotsup}\r\n"}
+ ], [], [], Args),
+
+ rtnode:run(
+ [{putline, ""},
+ {putline, "2."},
+ {expect, "2\r\n"},
+ {putline, "io:columns()."},
+ {expect, "{ok,90}\r\n"},
+ {putline,"io:rows()."},
+ {expect, "{ok,40}\r\n"}],
+ [],
+ "stty rows 40; stty columns 90; ",
+ Args);
test_columns_and_rows(new, _Args) ->
- rtnode([{putline, ""},
- {expect, "1> $"},
- {putline, "2."},
- {expect, "\r\n2\r\n"},
- {expect, "> $"},
- {putline, "io:columns()."},
- {expect, "{ok,80}\r\n"},
- {expect, "> $"},
- {putline, "io:rows()."},
- {expect, "\r\n{ok,24}\r\n"}
- ]),
-
- rtnode([{putline, ""},
- {expect, "1> $"},
- {putline, "2."},
- {expect, "\r\n2\r\n"},
- {expect, "> $"},
- {putline, "io:columns()."},
- {expect, "\r\n{ok,90}\r\n"},
- {expect, "> $"},
- {putline, "io:rows()."},
- {expect, "\r\n{ok,40}\r\n"}],
- [],
- "stty rows 40; stty columns 90; ").
+ rtnode:run(
+ [{putline, ""},
+ {expect, "1> $"},
+ {putline, "2."},
+ {expect, "\r\n2\r\n"},
+ {expect, "> $"},
+ {putline, "io:columns()."},
+ {expect, "{ok,80}\r\n"},
+ {expect, "> $"},
+ {putline, "io:rows()."},
+ {expect, "\r\n{ok,24}\r\n"}
+ ]),
+
+ rtnode:run(
+ [{putline, ""},
+ {expect, "1> $"},
+ {putline, "2."},
+ {expect, "\r\n2\r\n"},
+ {expect, "> $"},
+ {putline, "io:columns()."},
+ {expect, "\r\n{ok,90}\r\n"},
+ {expect, "> $"},
+ {putline, "io:rows()."},
+ {expect, "\r\n{ok,40}\r\n"}],
+ [],
+ "stty rows 40; stty columns 90; ").
%% Tests that exit of initial shell restarts shell.
exit_initial(Config) when is_list(Config) ->
@@ -258,36 +260,38 @@ exit_initial(Config) when is_list(Config) ->
ok.
test_exit_initial(old) ->
- rtnode([{putline, ""},
- {putline, "2."},
- {expect, "2\r\n"},
- {putline, "exit()."},
- {expect, "Eshell"},
- {putline, ""},
- {putline, "35."},
- {expect, "35\r\n"}],
- [], [], ["-oldshell"]);
+ rtnode:run(
+ [{putline, ""},
+ {putline, "2."},
+ {expect, "2\r\n"},
+ {putline, "exit()."},
+ {expect, "Eshell"},
+ {putline, ""},
+ {putline, "35."},
+ {expect, "35\r\n"}],
+ [], [], ["-oldshell"]);
test_exit_initial(new) ->
- rtnode([{putline, ""},
- {expect, "1> $"},
- {putline, "2."},
- {expect, "2"},
- {putline,"exit()."},
- {expect, "Eshell"},
- {expect, "1> $"},
- {putline, "35."},
- {expect, "35\r\n"}]).
+ rtnode:run(
+ [{putline, ""},
+ {expect, "1> $"},
+ {putline, "2."},
+ {expect, "2"},
+ {putline,"exit()."},
+ {expect, "Eshell"},
+ {expect, "1> $"},
+ {putline, "35."},
+ {expect, "35\r\n"}]).
stop_during_init(Config) when is_list(Config) ->
- {RunErl,_ToErl,[Erl|ErlArgs]} = get_progs(),
- case create_tempdir() of
+ {RunErl,_ToErl,[Erl|ErlArgs]} = rtnode:get_progs(),
+ case rtnode:create_tempdir() of
{error, Reason} ->
{skip, Reason};
Tempdir ->
XArg = " -kernel shell_history enabled -s init stop",
- start_runerl_command(RunErl, Tempdir, "\\\""++Erl++"\\\""++ErlArgs++XArg),
- Logs = rtnode_read_logs(Tempdir),
- rtnode_dump_logs(Logs),
+ rtnode:start_runerl_command(RunErl, Tempdir, "\\\""++Erl++"\\\""++ErlArgs++XArg),
+ Logs = rtnode:read_logs(Tempdir),
+ rtnode:dump_logs(Logs),
nomatch = binary:match(map_get("erlang.log.1", Logs),
<<"*** ERROR: Shell process terminated! ***">>),
ok
@@ -310,15 +314,16 @@ wrap(Config) when is_list(Config) ->
case proplists:get_value(default_shell, Config) of
new ->
As = lists:duplicate(20,"a"),
- rtnode([{putline, "io:columns()."},
- {expect, "{ok,20}\r\n"},
- {putline, ["io:format(\"~s\",[lists:duplicate(20,\"a\")])."]},
- {expect, As ++ " \b"},
- {putline, ["io:format(\"~s~n~s\",[lists:duplicate(20,\"a\"),lists:duplicate(20,\"a\")])."]},
- {expect, As ++ "\r\n" ++ As ++ " \b"}
- ],
- [],
- "stty rows 40; stty columns 20; ");
+ rtnode:run(
+ [{putline, "io:columns()."},
+ {expect, "{ok,20}\r\n"},
+ {putline, ["io:format(\"~s\",[lists:duplicate(20,\"a\")])."]},
+ {expect, As ++ " \b"},
+ {putline, ["io:format(\"~s~n~s\",[lists:duplicate(20,\"a\"),lists:duplicate(20,\"a\")])."]},
+ {expect, As ++ "\r\n" ++ As ++ " \b"}
+ ],
+ [],
+ "stty rows 40; stty columns 20; ");
_ ->
ok
end,
@@ -333,61 +338,61 @@ wrap(Config) when is_list(Config) ->
%% commands.
shell_history(Config) when is_list(Config) ->
Path = shell_history_path(Config, "basic"),
- rtnode([
- {putline, "echo1."},
- {expect, "echo1\r\n"},
- {putline, "echo2."},
- {expect, "echo2\r\n"},
- {putline, "echo3."},
- {expect, "echo3\r\n"},
- {putline, "echo4."},
- {expect, "echo4\r\n"},
- {putline, "echo5."},
- {expect, "echo5\r\n"}
- ], [], [], mk_history_param(Path)),
+ rtnode:run(
+ [{putline, "echo1."},
+ {expect, "echo1\r\n"},
+ {putline, "echo2."},
+ {expect, "echo2\r\n"},
+ {putline, "echo3."},
+ {expect, "echo3\r\n"},
+ {putline, "echo4."},
+ {expect, "echo4\r\n"},
+ {putline, "echo5."},
+ {expect, "echo5\r\n"}
+ ], [], [], mk_history_param(Path)),
receive after 1000 -> ok end,
- rtnode([
- {sleep,100},
- {putline, ""},
- %% the init:stop that stopped the node is dropped
- {putdata, [$\^p]}, {expect, "echo5[.]$"},
- {putdata, [$\n]},
- {expect, "echo5\r\n"},
- {putdata, [$\^p]}, {expect, "echo5[.]$"},
- {putdata, [$\^p]}, {expect, "echo4[.]$"},
- {putdata, [$\^p]}, {expect, "echo3[.]$"},
- {putdata, [$\^p]}, {expect, "echo2[.]$"},
- {putdata, [$\^n]}, {expect, "echo3[.]$"},
- {putdata, [$\^n]}, {expect, "echo4[.]$"},
- {putdata, [$\^b]}, {sleep,50}, %% the echo4. (cursor moved one left)
- {putline, ["ECHO"]},
- {expect, "echo4ECHO\r\n"}
- ], [], [],
- mk_history_param(Path)),
+ rtnode:run(
+ [{sleep,100},
+ {putline, ""},
+ %% the init:stop that stopped the node is dropped
+ {putdata, [$\^p]}, {expect, "echo5[.]$"},
+ {putdata, [$\n]},
+ {expect, "echo5\r\n"},
+ {putdata, [$\^p]}, {expect, "echo5[.]$"},
+ {putdata, [$\^p]}, {expect, "echo4[.]$"},
+ {putdata, [$\^p]}, {expect, "echo3[.]$"},
+ {putdata, [$\^p]}, {expect, "echo2[.]$"},
+ {putdata, [$\^n]}, {expect, "echo3[.]$"},
+ {putdata, [$\^n]}, {expect, "echo4[.]$"},
+ {putdata, [$\^b]}, {sleep,50}, %% the echo4. (cursor moved one left)
+ {putline, ["ECHO"]},
+ {expect, "echo4ECHO\r\n"}
+ ], [], [],
+ mk_history_param(Path)),
ok.
shell_history_resize(Config) ->
Path = shell_history_path(Config, "resize"),
- rtnode([
- {putline, "echo."},
- {expect, "echo\r\n"},
- {putline, "echo2."},
- {expect, "echo2\r\n"}
- ], [], [], ["-kernel","shell_history_file_bytes","123456"] ++
- mk_history_param(Path)),
+ rtnode:run(
+ [{putline, "echo."},
+ {expect, "echo\r\n"},
+ {putline, "echo2."},
+ {expect, "echo2\r\n"}
+ ], [], [], ["-kernel","shell_history_file_bytes","123456"] ++
+ mk_history_param(Path)),
{ok, Logs} =
- rtnode([
- {sleep,100},
- {putline, ""},
- {putdata, [$\^p]}, {expect, "echo2[.]$$"},
- {putdata, [$\^p]}, {expect, "echo[.]$"},
- {putdata, [$\n]},
- {expect, "echo"}
- ], [], [], ["-kernel","shell_history_file_bytes","654321"] ++
- mk_history_param(Path)),
-
- rtnode_check_logs(
+ rtnode:run(
+ [{sleep,100},
+ {putline, ""},
+ {putdata, [$\^p]}, {expect, "echo2[.]$$"},
+ {putdata, [$\^p]}, {expect, "echo[.]$"},
+ {putdata, [$\n]},
+ {expect, "echo"}
+ ], [], [], ["-kernel","shell_history_file_bytes","654321"] ++
+ mk_history_param(Path)),
+
+ rtnode:check_logs(
"erlang.log.1",
"The configured log history file size is different from the size "
"of the log file on disk", Logs),
@@ -405,24 +410,24 @@ shell_history_eaccess(Config) ->
%% Cannot create history log in folder
{ok, Logs1} =
- rtnode([
- {putline, "echo."},
- {expect, "echo\r\n"}
- ], [], [], mk_history_param(Path)),
+ rtnode:run(
+ [{putline, "echo."},
+ {expect, "echo\r\n"}
+ ], [], [], mk_history_param(Path)),
ct:pal("~p",[Logs1]),
- rtnode_check_logs("erlang.log.1", "Error handling file", Logs1),
+ rtnode:check_logs("erlang.log.1", "Error handling file", Logs1),
%% shell_docs recursively creates the folder to store the
%% logs. This test checks that erlang still starts if we
%% cannot create the folders to the path.
{ok, Logs2} =
- rtnode([
- {putline, "echo."},
- {expect, "echo\r\n"}
- ], [], [], mk_history_param(filename:join(Path,"logs"))),
+ rtnode:run(
+ [{putline, "echo."},
+ {expect, "echo\r\n"}
+ ], [], [], mk_history_param(filename:join(Path,"logs"))),
- rtnode_check_logs("erlang.log.1", "Error handling file", Logs2)
+ rtnode:check_logs("erlang.log.1", "Error handling file", Logs2)
after
file:write_file_info(Path, Info)
@@ -436,15 +441,15 @@ shell_history_repair(Config) ->
shell_history_halt(Path),
{ok, Logs} =
- rtnode([
- {putline, ""},
- {putdata, [$\^p]}, {expect, "echo[.]$"},
- {putdata, [$\n]},
- {expect, "echo\r\n"}
- ], [], [], mk_history_param(Path)),
+ rtnode:run(
+ [{putline, ""},
+ {putdata, [$\^p]}, {expect, "echo[.]$"},
+ {putdata, [$\n]},
+ {expect, "echo\r\n"}
+ ], [], [], mk_history_param(Path)),
%% The regexp below checks that he string is NOT part of the log
- rtnode_check_logs("erlang.log.1",
+ rtnode:check_logs("erlang.log.1",
"The shell history log file was corrupted and was repaired",
false,
Logs),
@@ -462,14 +467,14 @@ shell_history_repair_corrupt(Config) ->
ok = file:close(D),
{ok, Logs} =
- rtnode([
- {putline, ""},
- {putdata, [$\^p]}, {expect, "echo[.]$"},
- {putdata, [$\n]},
- {expect, "echo\r\n"}
- ], [], [], mk_history_param(Path)),
-
- rtnode_check_logs("erlang.log.1",
+ rtnode:run(
+ [{putline, ""},
+ {putdata, [$\^p]}, {expect, "echo[.]$"},
+ {putdata, [$\n]},
+ {expect, "echo\r\n"}
+ ], [], [], mk_history_param(Path)),
+
+ rtnode:check_logs("erlang.log.1",
"The shell history log file was corrupted and was repaired.",
Logs),
ok.
@@ -478,11 +483,12 @@ shell_history_corrupt(Config) ->
Path = shell_history_path(Config, "corrupt"),
%% We initialize the shell history log with a known value.
- rtnode([{putline, "echo."},
- {expect, "echo\r\n"},
- {putline, "echo2."},
- {expect, "echo2\r\n"}
- ], [], [], mk_history_param(Path)),
+ rtnode:run(
+ [{putline, "echo."},
+ {expect, "echo\r\n"},
+ {putline, "echo2."},
+ {expect, "echo2\r\n"}
+ ], [], [], mk_history_param(Path)),
%% We corrupt the disklog.
{ok, D} = file:open(filename:join(Path,"erlang-shell-log.1"), [read, append]),
@@ -490,36 +496,36 @@ shell_history_corrupt(Config) ->
ok = file:close(D),
{ok, Logs} =
- rtnode([
- {putline, ""},
- {putdata, [$\^p]}, {expect, "echo2[.]$"},
- {putdata, [$\^p]}, {expect, "echo[.]$"},
- {putdata, [$\n]},
- {expect, "echo\r\n"}
- ], [], [], mk_history_param(Path)),
-
- rtnode_check_logs("erlang.log.1", "Invalid chunk in the file", Logs),
+ rtnode:run(
+ [{putline, ""},
+ {putdata, [$\^p]}, {expect, "echo2[.]$"},
+ {putdata, [$\^p]}, {expect, "echo[.]$"},
+ {putdata, [$\n]},
+ {expect, "echo\r\n"}
+ ], [], [], mk_history_param(Path)),
+
+ rtnode:check_logs("erlang.log.1", "Invalid chunk in the file", Logs),
ok.
%% Stop the node without closing the log.
shell_history_halt(Path) ->
try
- rtnode([
- {putline, "echo."},
- {expect, "echo\r\n"},
- {sleep, 2500}, % disk_log internal cache timer is 2000 ms
- {putline, "halt(0)."},
- {expect, "\r\n"},
- {sleep, 1000} %% wait for node to terminate
- ], [], [], mk_history_param(Path))
+ rtnode:run(
+ [{putline, "echo."},
+ {expect, "echo\r\n"},
+ {sleep, 2500}, % disk_log internal cache timer is 2000 ms
+ {putline, "halt(0)."},
+ {expect, "\r\n"},
+ {sleep, 1000} %% wait for node to terminate
+ ], [], [], mk_history_param(Path))
catch
_:_ ->
ok
end.
shell_history_path(Config, TestCase) ->
- filename:join([proplists:get_value(priv_dir, Config),
- "shell_history", TestCase]).
+ filename:join([proplists:get_value(priv_dir, Config),
+ "shell_history", TestCase]).
mk_history_param(Path) ->
["-kernel","shell_history","enabled",
@@ -529,63 +535,65 @@ mk_history_param(Path) ->
shell_history_custom(_Config) ->
%% Up key: Ctrl + P = Cp=[$\^p]
- rtnode([{expect, "1> $"},
- %% {putline, ""},
- {putdata, [$\^p]}, {expect, "0[.]"},
- {putdata, [$\n]},
- {expect, "0\r\n"},
- {putline, "echo."},
- {expect, "!echo\r\n"} % exclamation mark is printed by custom history module
- ], [], [], ["-kernel","shell_history",atom_to_list(?MODULE),
- "-pz",filename:dirname(code:which(?MODULE))]),
+ rtnode:run(
+ [{expect, "1> $"},
+ %% {putline, ""},
+ {putdata, [$\^p]}, {expect, "0[.]"},
+ {putdata, [$\n]},
+ {expect, "0\r\n"},
+ {putline, "echo."},
+ {expect, "!echo\r\n"} % exclamation mark is printed by custom history module
+ ], [], [], ["-kernel","shell_history",atom_to_list(?MODULE),
+ "-pz",filename:dirname(code:which(?MODULE))]),
ok.
shell_history_custom_errors(_Config) ->
%% Check that we can start with a node with an undefined
%% provider module.
- rtnode([{putline, "echo."},
- {expect, "echo\r\n"}
- ], [], [], ["-kernel","shell_history","very_broken",
- "-pz",filename:dirname(code:which(?MODULE))]),
+ rtnode:run(
+ [{putline, "echo."},
+ {expect, "echo\r\n"}
+ ], [], [], ["-kernel","shell_history","very_broken",
+ "-pz",filename:dirname(code:which(?MODULE))]),
%% Check that we can start with a node with a provider module
%% that crashes in load/0.
- rtnode([
- {putline, "echo."},
- {expect, "echo\r\n"}
- ], [], [], ["-kernel","shell_history",atom_to_list(?MODULE),
- "-kernel","provider_load","crash",
- "-pz",filename:dirname(code:which(?MODULE))]),
+ rtnode:run(
+ [{putline, "echo."},
+ {expect, "echo\r\n"}
+ ], [], [], ["-kernel","shell_history",atom_to_list(?MODULE),
+ "-kernel","provider_load","crash",
+ "-pz",filename:dirname(code:which(?MODULE))]),
%% Check that we can start with a node with a provider module
%% that return incorrect in load/0.
- rtnode([
- {putline, "echo."},
- {expect, "echo\r\n"}
- ], [], [], ["-kernel","shell_history",atom_to_list(?MODULE),
- "-kernel","provider_load","badreturn",
- "-pz",filename:dirname(code:which(?MODULE))]),
+ rtnode:run(
+ [{putline, "echo."},
+ {expect, "echo\r\n"}
+ ], [], [], ["-kernel","shell_history",atom_to_list(?MODULE),
+ "-kernel","provider_load","badreturn",
+ "-pz",filename:dirname(code:which(?MODULE))]),
%% Check that we can start with a node with a provider module
%% that crashes in load/0.
- rtnode([
- {putline, "echo."},
- {expect, "(Disabling shell history logging.|echo)\r\n"},
- {expect, "(Disabling shell history logging.|echo)\r\n"}
- ], [], [], ["-kernel","shell_history",atom_to_list(?MODULE),
- "-kernel","provider_add","crash",
- "-pz",filename:dirname(code:which(?MODULE))]),
+ rtnode:run(
+ [{putline, "echo."},
+ {expect, "(Disabling shell history logging.|echo)\r\n"},
+ {expect, "(Disabling shell history logging.|echo)\r\n"}
+ ], [], [], ["-kernel","shell_history",atom_to_list(?MODULE),
+ "-kernel","provider_add","crash",
+ "-pz",filename:dirname(code:which(?MODULE))]),
%% Check that we can start with a node with a provider module
%% that return incorrect in load/0.
- rtnode([
- {putline, "echo."},
- {expect, "It returned {error,badreturn}.\r\n"},
- {expect, "echo\r\n"}
- ], [], [], ["-kernel","shell_history",atom_to_list(?MODULE),
- "-kernel","provider_add","badreturn",
- "-pz",filename:dirname(code:which(?MODULE))]),
+ rtnode:run(
+ [{putline, "echo."},
+ {expect, "It returned {error,badreturn}.\r\n"},
+ {expect, "echo\r\n"}
+ ], [], [], ["-kernel","shell_history",atom_to_list(?MODULE),
+ "-kernel","provider_add","badreturn",
+ "-pz",filename:dirname(code:which(?MODULE))]),
ok.
@@ -619,59 +627,60 @@ job_control_local(Config) when is_list(Config) ->
{skip,"No new shell found"};
new ->
%% New shell tests
- rtnode([{putline, ""},
- {expect, "1> $"},
- {putline, "2."},
- {expect, "\r\n2\r\n"},
- {putline, "\^g"},
- {expect, "--> $"},
- {putline, "s"},
- {expect, "--> $"},
- {putline, "c"},
- {expect, "\r\nEshell"},
- {expect, "1> $"},
- {putline, "35."},
- {expect, "\r\n35\r\n"},
- {expect, "2> $"},
- {putline, "receive M -> M end.\r\n"},
- {putline, "\^g"},
- {expect, "--> $"},
- {putline, "i 3"},
- {expect, "Unknown job"},
- {expect, "--> $"},
- {putline, "i 2"},
- {expect, "--> $"},
- {putline, "c"},
- {expect, "[*][*] exception exit: killed"},
- {expect, "[23]>"},
- {putline, "\^g"},
- {expect, "--> $"},
- {putline, "k 3"},
- {expect, "Unknown job"},
- {expect, "--> $"},
- {putline, "k 2"},
- {expect, "--> $"},
- {putline, "k"},
- {expect, "Unknown job"},
- {expect, "--> $"},
- {putline, "c"},
- {expect, "Unknown job"},
- {expect, "--> $"},
- {putline, "i"},
- {expect, "Unknown job"},
- {expect, "--> $"},
- {putline, "?"},
- {expect, "this message"},
- {expect, "--> $"},
- {putline, "h"},
- {expect, "this message"},
- {expect, "--> $"},
- {putline, "c 1"},
- {expect, "\r\n"},
- {putline, "35."},
- {expect, "\r\n35\r\n"},
- {expect, "[23]> $"}
- ]),
+ rtnode:run(
+ [{putline, ""},
+ {expect, "1> $"},
+ {putline, "2."},
+ {expect, "\r\n2\r\n"},
+ {putline, "\^g"},
+ {expect, "--> $"},
+ {putline, "s"},
+ {expect, "--> $"},
+ {putline, "c"},
+ {expect, "\r\nEshell"},
+ {expect, "1> $"},
+ {putline, "35."},
+ {expect, "\r\n35\r\n"},
+ {expect, "2> $"},
+ {putline, "receive M -> M end.\r\n"},
+ {putline, "\^g"},
+ {expect, "--> $"},
+ {putline, "i 3"},
+ {expect, "Unknown job"},
+ {expect, "--> $"},
+ {putline, "i 2"},
+ {expect, "--> $"},
+ {putline, "c"},
+ {expect, "[*][*] exception exit: killed"},
+ {expect, "[23]>"},
+ {putline, "\^g"},
+ {expect, "--> $"},
+ {putline, "k 3"},
+ {expect, "Unknown job"},
+ {expect, "--> $"},
+ {putline, "k 2"},
+ {expect, "--> $"},
+ {putline, "k"},
+ {expect, "Unknown job"},
+ {expect, "--> $"},
+ {putline, "c"},
+ {expect, "Unknown job"},
+ {expect, "--> $"},
+ {putline, "i"},
+ {expect, "Unknown job"},
+ {expect, "--> $"},
+ {putline, "?"},
+ {expect, "this message"},
+ {expect, "--> $"},
+ {putline, "h"},
+ {expect, "this message"},
+ {expect, "--> $"},
+ {putline, "c 1"},
+ {expect, "\r\n"},
+ {putline, "35."},
+ {expect, "\r\n35\r\n"},
+ {expect, "[23]> $"}
+ ]),
ok
end.
@@ -681,7 +690,8 @@ job_control_remote(Config) when is_list(Config) ->
old ->
{skip,"No new shell found"};
_ ->
- {ok, Peer, NSNode} = ?CT_PEER(#{ peer_down => continue }),
+ {ok, Peer, NSNode} = ?CT_PEER(#{ args => ["-connect_all","false"],
+ peer_down => continue }),
try
test_remote_job_control(NSNode)
after
@@ -696,7 +706,8 @@ job_control_remote_noshell(Config) when is_list(Config) ->
old ->
{skip,"No new shell found"};
_ ->
- {ok, Peer, NSNode} = ?CT_PEER(#{ args => ["-noshell"],
+ {ok, Peer, NSNode} = ?CT_PEER(#{ name => peer:random_name(test_remote_job_control),
+ args => ["-connect_all","false","-noshell"],
peer_down => continue }),
try
test_remote_job_control(NSNode)
@@ -711,54 +722,55 @@ test_remote_job_control(Node) ->
receive die ->
ok
end
- end),
+ end),
PidStr = erpc:call(Node, erlang, pid_to_list, [Pid]),
true = erpc:call(Node, erlang, register, [kalaskula,Pid]),
PrintedNode = printed_atom(Node),
CookieString = printed_atom(erlang:get_cookie()),
- rtnode([{putline, ""},
- {putline, "erlang:get_cookie()."},
- {expect, "\r\n\\Q" ++ CookieString ++ "\\E"},
- {putdata, "\^g"},
- {expect, " --> $"},
- {putline, "r " ++ PrintedNode},
- {expect, "\r\n"},
- {putline, "j"},
- {expect, "1 {shell,start,\\[init]}"},
- {expect, "2[*] {\\Q"++PrintedNode++"\\E,shell,start,\\[]}"},
- {expect, " --> $"},
- {putline, "c"},
- {expect, "\r\n"},
- {expect, "Eshell"},
- {expect, "\\Q(" ++ atom_to_list(Node) ++")1> \\E$"},
- {putline, "whereis(kalaskula)."},
- {expect, PidStr},
- {putline, "kalaskula ! die."},
- {putline, "exit()."},
- {expect, "[*][*][*] Shell process terminated!"},
- {putdata, "\^g"},
- {expect, " --> $"},
- {putline, "j"},
- {expect, "1 {shell,start,\\[init]}"},
- {expect, " --> $"},
- {putline, "c"},
- {expect, "Unknown job"},
- {expect, " --> $"},
- {putline, "c 1"},
- {expect, "\r\n"},
- {putline, ""},
- {expect, "\\Q("++RemNode++"@\\E[^)]*\\)[12]> $"},
- {putdata, "\^g"},
- {expect, " --> $"},
- {putline, "j"},
- {expect, "1[*] {shell,start,\\[init]}"},
- {putline, "c"},
- {expect, "\r\n"},
- {sleep, 100},
- {putline, "35."},
- {expect, "\\Q("++RemNode++"@\\E[^)]*\\)[123]> $"}
- ], RemNode),
+ rtnode:run(
+ [{putline, ""},
+ {putline, "erlang:get_cookie()."},
+ {expect, "\r\n\\Q" ++ CookieString ++ "\\E"},
+ {putdata, "\^g"},
+ {expect, " --> $"},
+ {putline, "r " ++ PrintedNode},
+ {expect, "\r\n"},
+ {putline, "j"},
+ {expect, "1 {shell,start,\\[init]}"},
+ {expect, "2[*] {\\Q"++PrintedNode++"\\E,shell,start,\\[]}"},
+ {expect, " --> $"},
+ {putline, "c"},
+ {expect, "\r\n"},
+ {expect, "Eshell"},
+ {expect, "\\Q(" ++ atom_to_list(Node) ++")1> \\E$"},
+ {putline, "whereis(kalaskula)."},
+ {expect, PidStr},
+ {putline, "kalaskula ! die."},
+ {putline, "exit()."},
+ {expect, "[*][*][*] Shell process terminated!"},
+ {putdata, "\^g"},
+ {expect, " --> $"},
+ {putline, "j"},
+ {expect, "1 {shell,start,\\[init]}"},
+ {expect, " --> $"},
+ {putline, "c"},
+ {expect, "Unknown job"},
+ {expect, " --> $"},
+ {putline, "c 1"},
+ {expect, "\r\n"},
+ {putline, ""},
+ {expect, "\\Q("++RemNode++"@\\E[^)]*\\)[12]> $"},
+ {putdata, "\^g"},
+ {expect, " --> $"},
+ {putline, "j"},
+ {expect, "1[*] {shell,start,\\[init]}"},
+ {putline, "c"},
+ {expect, "\r\n"},
+ {sleep, 100},
+ {putline, "35."},
+ {expect, "\\Q("++RemNode++"@\\E[^)]*\\)[123]> $"}
+ ], RemNode),
Pid ! die,
ok.
@@ -769,20 +781,21 @@ ctrl_keys(_Config) ->
Cy = [$\^y],
Home = [27,$O,$H],
End = [27,$O,$F],
- rtnode([{putline,""},
- {putline,"2."},
- {expect,"2"},
- {putline,"\"hello "++Cw++"world\"."}, % test <CTRL>+W
- {expect,"\"world\""},
- {putline,"\"hello "++Cu++"\"world\"."}, % test <CTRL>+U
- {expect,"\"world\""},
- {putline,"world\"."++Home++"\"hello "}, % test <HOME>
- {expect,"\"hello world\""},
- {putline,"world"++Home++"\"hello "++End++"\"."}, % test <END>
- {expect,"\"hello world\""},
- {putline,"\"hello world\""++Cu++Cy++"."},
- {expect,"\"hello world\""}] ++
- wordLeft() ++ wordRight()),
+ rtnode:run(
+ [{putline,""},
+ {putline,"2."},
+ {expect,"2"},
+ {putline,"\"hello "++Cw++"world\"."}, % test <CTRL>+W
+ {expect,"\"world\""},
+ {putline,"\"hello "++Cu++"\"world\"."}, % test <CTRL>+U
+ {expect,"\"world\""},
+ {putline,"world\"."++Home++"\"hello "}, % test <HOME>
+ {expect,"\"hello world\""},
+ {putline,"world"++Home++"\"hello "++End++"\"."}, % test <END>
+ {expect,"\"hello world\""},
+ {putline,"\"hello world\""++Cu++Cy++"."},
+ {expect,"\"hello world\""}] ++
+ wordLeft() ++ wordRight()),
ok.
wordLeft() ->
@@ -822,14 +835,15 @@ remsh_basic(Config) when is_list(Config) ->
%% Test that remsh works with explicit -sname.
HostNode = atom_to_list(?FUNCTION_NAME) ++ "_host",
HostNodeStr = printed_atom(list_to_atom(HostNode ++ "@" ++ Host)),
- rtnode(PreCmds ++
- [{putline,"nodes()."},
- {expect, "\\Q" ++ HostNodeStr ++ "\\E"}] ++
- PostCmds,
- HostNode, " ", "-remsh " ++ TargetNodeStr),
+ rtnode:run(
+ PreCmds ++
+ [{putline,"nodes()."},
+ {expect, "\\Q" ++ HostNodeStr ++ "\\E"}] ++
+ PostCmds,
+ HostNode, " ", "-remsh " ++ TargetNodeStr),
%% Test that remsh works without -sname.
- rtnode(PreCmds ++ PostCmds, [], " ", "-remsh " ++ TargetNodeStr),
+ rtnode:run(PreCmds ++ PostCmds, [], " ", "-remsh " ++ TargetNodeStr),
peer:stop(Peer),
@@ -854,28 +868,30 @@ remsh_longnames(Config) when is_list(Config) ->
"@127.0.0.1";
_ -> ""
end,
- case rtstart(" -name " ++ atom_to_list(?FUNCTION_NAME)++Domain) of
- {ok, _SRPid, STPid, SState} ->
+ case rtnode:start(" -name " ++ atom_to_list(?FUNCTION_NAME)++Domain) of
+ {ok, _SRPid, STPid, SNode, SState} ->
try
- {ok, _CRPid, CTPid, CState} =
- rtstart("-name undefined" ++ Domain ++
- " -remsh " ++ atom_to_list(?FUNCTION_NAME)),
+ {ok, _CRPid, CTPid, CNode, CState} =
+ rtnode:start("-name undefined" ++ Domain ++
+ " -remsh " ++ atom_to_list(?FUNCTION_NAME)),
try
- ok = send_commands(
+ ok = rtnode:send_commands(
+ SNode,
STPid,
[{putline, ""},
{putline, "node()."},
{expect, "\\Q" ++ atom_to_list(?FUNCTION_NAME) ++ "\\E"}], 1),
- ok = send_commands(
+ ok = rtnode:send_commands(
+ CNode,
CTPid,
[{putline, ""},
{putline, "node()."},
{expect, "\\Q" ++ atom_to_list(?FUNCTION_NAME) ++ "\\E"} | quit_hosting_node()], 1)
after
- rtnode_dump_logs(rtstop(CState))
+ rtnode:dump_logs(rtnode:stop(CState))
end
after
- rtnode_dump_logs(rtstop(SState))
+ rtnode:dump_logs(rtnode:stop(SState))
end;
Else ->
Else
@@ -884,496 +900,35 @@ remsh_longnames(Config) when is_list(Config) ->
%% Test that -remsh works without epmd.
remsh_no_epmd(Config) when is_list(Config) ->
EPMD_ARGS = "-start_epmd false -erl_epmd_port 12345 ",
- case rtstart([],"ERL_EPMD_PORT=12345 ",
- EPMD_ARGS ++ " -sname " ++ atom_to_list(?FUNCTION_NAME)) of
- {ok, _SRPid, STPid, SState} ->
+ case rtnode:start([],"ERL_EPMD_PORT=12345 ",
+ EPMD_ARGS ++ " -sname " ++ atom_to_list(?FUNCTION_NAME)) of
+ {ok, _SRPid, STPid, SNode, SState} ->
try
- ok = send_commands(
+ ok = rtnode:send_commands(
+ SNode,
STPid,
[{putline, ""},
{putline, "node()."},
{expect, "\\Q" ++ atom_to_list(?FUNCTION_NAME) ++ "\\E"}], 1),
- {ok, _CRPid, CTPid, CState} =
- rtstart([],"ERL_EPMD_PORT=12345 ",
- EPMD_ARGS ++ " -remsh "++atom_to_list(?FUNCTION_NAME)),
+ {ok, _CRPid, CTPid, CNode, CState} =
+ rtnode:start([],"ERL_EPMD_PORT=12345 ",
+ EPMD_ARGS ++ " -remsh "++atom_to_list(?FUNCTION_NAME)),
try
- ok = send_commands(
+ ok = rtnode:send_commands(
+ CNode,
CTPid,
[{putline, ""},
{putline, "node()."},
{expect, "\\Q" ++ atom_to_list(?FUNCTION_NAME) ++ "\\E"} | quit_hosting_node()], 1)
after
- rtstop(CState)
+ rtnode:stop(CState)
end
after
- rtstop(SState)
+ rtnode:stop(SState)
end;
Else ->
Else
end.
-rtnode(C) ->
- rtnode(C, [], [], []).
-
-rtnode(C, N) ->
- rtnode(C, N, [], []).
-
-rtnode(Commands, Nodename, ErlPrefix) ->
- rtnode(Commands, Nodename, ErlPrefix, []).
-
-rtnode(Commands, Nodename, ErlPrefix, Args) ->
- case rtstart(Nodename, ErlPrefix, Args) of
- {ok, _SPid, CPid, RTState} ->
- Res = catch send_commands(CPid, Commands, 1),
- Logs = rtstop(RTState),
- case Res of
- ok ->
- rtnode_dump_logs(Logs),
- ok;
- _ ->
- rtnode_dump_logs(Logs),
- ok = Res
- end,
- {ok, Logs};
- Skip ->
- Skip
- end.
-
-rtstart(Args) ->
- rtstart([], " ", Args).
-
-rtstart(Nodename, ErlPrefix, Args) ->
- case get_progs() of
- {error,_Reason} ->
- {skip,"No runerl present"};
- {RunErl,ToErl,[Erl|ErlArgs] = ErlWArgs} ->
- case create_tempdir() of
- {error, Reason2} ->
- {skip, Reason2};
- Tempdir when ErlPrefix =/= [] ->
- SPid =
- start_runerl_node(RunErl,
- ErlPrefix++"\\\""++Erl++"\\\" "++
- lists:join($\s, ErlArgs),
- Tempdir,Nodename,Args),
- CPid = start_toerl_server(ToErl,Tempdir,undefined),
- {ok, SPid, CPid, {CPid, SPid, ToErl, Tempdir}};
- Tempdir ->
- SPid = start_peer_runerl_node(RunErl,ErlWArgs,Tempdir,Nodename,Args),
- CPid = start_toerl_server(ToErl,Tempdir,SPid),
- {ok, SPid, CPid, {CPid, SPid, ToErl, Tempdir}}
- end
- end.
-
-rtstop({CPid, SPid, ToErl, Tempdir}) ->
- %% Unlink from peer so that we don't crash when peer quits
- unlink(SPid),
- case stop_runerl_node(CPid) of
- {error,_} ->
- catch rtstop_try_harder(ToErl, Tempdir, SPid);
- _ ->
- ok
- end,
- wait_for_runerl_server(SPid),
- Logs = rtnode_read_logs(Tempdir),
- file:del_dir_r(Tempdir),
- Logs.
-
-rtstop_try_harder(ToErl, Tempdir, SPid) ->
- CPid = start_toerl_server(ToErl, Tempdir, SPid),
- ok = send_commands(CPid,
- [{putline,[7]},
- {expect, " --> $"},
- {putline, "s"},
- {putline, "c"},
- {putline, ""}], 1),
- stop_runerl_node(CPid).
-
-timeout(longest) ->
- timeout(long) + timeout(normal);
-timeout(long) ->
- 2 * timeout(normal);
-timeout(short) ->
- timeout(normal) div 10;
-timeout(normal) ->
- 10000 * test_server:timetrap_scale_factor().
-
-send_commands(CPid, [{sleep, X}|T], N) ->
- ?dbg({sleep, X}),
- receive
- after X ->
- send_commands(CPid, T, N+1)
- end;
-send_commands(CPid, [{expect, Expect}|T], N) when is_list(Expect) ->
- ?dbg(Exp),
- case command(CPid, {expect, [Expect], timeout(normal)}) of
- ok ->
- send_commands(CPid, T, N + 1);
- {expect_timeout, Got} ->
- ct:pal("expect timed out waiting for ~p\ngot: ~p\n", [Expect,Got]),
- {error, timeout};
- Other ->
- Other
- end;
-send_commands(CPid, [{putline, Line}|T], N) ->
- send_commands(CPid, [{putdata, Line ++ "\n"}|T], N);
-send_commands(CPid, [{putdata, Data}|T], N) ->
- ?dbg({putdata, Data}),
- case command(CPid, {send_data, Data}) of
- ok ->
- send_commands(CPid, T, N+1);
- Error ->
- Error
- end;
-send_commands(_CPid, [], _) ->
- ok.
-
-command(Pid, Req) ->
- Timeout = timeout(longest),
- Ref = erlang:monitor(process, Pid),
- Pid ! {self(), Ref, Req},
- receive
- {Ref, Reply} ->
- erlang:demonitor(Ref, [flush]),
- Reply;
- {'DOWN', Ref, _, _, Reason} ->
- {error, Reason}
- after Timeout ->
- io:format("timeout while executing ~p\n", [Req]),
- {error, timeout}
- end.
-
-wait_for_runerl_server(SPid) ->
- Ref = erlang:monitor(process, SPid),
- Timeout = timeout(long),
- receive
- {'DOWN', Ref, process, SPid, _Reason} ->
- ok
- after Timeout ->
- {error, runerl_server_timeout}
- end.
-
-stop_runerl_node(CPid) ->
- Ref = erlang:monitor(process, CPid),
- CPid ! {self(), kill_emulator},
- Timeout = timeout(longest),
- receive
- {'DOWN', Ref, process, CPid, noproc} ->
- ok;
- {'DOWN', Ref, process, CPid, normal} ->
- ok;
- {'DOWN', Ref, process, CPid, {error, Reason}} ->
- {error, Reason}
- after Timeout ->
- {error, toerl_server_timeout}
- end.
-
-get_progs() ->
- case os:type() of
- {unix,freebsd} ->
- {error,"Can't use run_erl on FreeBSD"};
- {unix,openbsd} ->
- {error,"Can't use run_erl on OpenBSD"};
- {unix,_} ->
- RunErl = find_executable("run_erl"),
- ToErl = find_executable("to_erl"),
- Erl = string:split(ct:get_progname()," ",all),
- {RunErl, ToErl, Erl};
- _ ->
- {error,"Not a Unix OS"}
- end.
-
-find_executable(Name) ->
- case os:find_executable(Name) of
- Prog when is_list(Prog) ->
- Prog;
- false ->
- throw("Could not find " ++ Name)
- end.
-
-create_tempdir() ->
- create_tempdir(filename:join(["/tmp","rtnode"++os:getpid()]),$A).
-
-create_tempdir(Dir,X) when X > $Z, X < $a ->
- create_tempdir(Dir,$a);
-create_tempdir(Dir,X) when X > $z ->
- Estr = lists:flatten(
- io_lib:format("Unable to create ~s, reason eexist",
- [Dir++[$z]])),
- {error, Estr};
-create_tempdir(Dir0, Ch) ->
- %% Expect fairly standard unix.
- Dir = Dir0++[Ch],
- case file:make_dir(Dir) of
- {error, eexist} ->
- create_tempdir(Dir0, Ch+1);
- {error, Reason} ->
- Estr = lists:flatten(
- io_lib:format("Unable to create ~s, reason ~p",
- [Dir,Reason])),
- {error,Estr};
- ok ->
- Dir
- end.
-
-start_runerl_node(RunErl,Erl,Tempdir,Nodename,Args) ->
- XArg = case Nodename of
- [] ->
- [];
- _ ->
- " -sname "++(if is_atom(Nodename) -> atom_to_list(Nodename);
- true -> Nodename
- end)++
- " -setcookie "++atom_to_list(erlang:get_cookie())
- end ++ " " ++ Args,
- spawn(fun() -> start_runerl_command(RunErl, Tempdir, Erl++XArg) end).
-
-start_runerl_command(RunErl, Tempdir, Cmd) ->
- FullCmd = "\""++RunErl++"\" "++Tempdir++"/ "++Tempdir++" \""++Cmd++"\"",
- ct:pal("~ts",[FullCmd]),
- os:cmd(FullCmd).
-
-start_peer_runerl_node(RunErl,Erl,Tempdir,[],Args) ->
- start_peer_runerl_node(RunErl,Erl,Tempdir,peer:random_name(),Args);
-start_peer_runerl_node(RunErl,Erl,Tempdir,Nodename,Args) ->
- {ok, Peer, _Node} =
- ?CT_PEER(#{ name => Nodename,
- exec => {RunErl,Erl},
- detached => false,
- shutdown => 10000,
- post_process_args =>
- fun(As) ->
- [Tempdir++"/",Tempdir,
- lists:flatten(
- lists:join(
- " ",[[$',A,$'] || A <- As]))]
- end,
- args => Args }),
- Peer.
-
-start_toerl_server(ToErl,Tempdir,SPid) ->
- Pid = spawn(?MODULE,toerl_server,[self(),ToErl,Tempdir,SPid]),
- receive
- {Pid,started} ->
- Pid;
- {Pid,error,Reason} ->
- {error,Reason}
- end.
-
-try_to_erl(_Command, 0) ->
- {error, cannot_to_erl};
-try_to_erl(Command, N) ->
- ?dbg({?LINE,N}),
- Port = open_port({spawn, Command},[eof]),
- Timeout = timeout(short) div 2,
- receive
- {Port, eof} ->
- timer:sleep(Timeout),
- try_to_erl(Command, N-1)
- after Timeout ->
- ?dbg(Port),
- Port
- end.
-
-toerl_server(Parent, ToErl, TempDir, SPid) ->
- Port = try_to_erl("\""++ToErl++"\" "++TempDir++"/ 2>/dev/null", 8),
- case Port of
- P when is_port(P) ->
- Parent ! {self(),started};
- {error,Other} ->
- Parent ! {self(),error,Other},
- exit(Other)
- end,
-
- State = #{port => Port, acc => [], spid => SPid},
- case toerl_loop(State) of
- normal ->
- ok;
- {error, Reason} ->
- error_logger:error_msg("toerl_server exit with reason ~p~n",
- [Reason]),
- exit(Reason)
- end.
-
-toerl_loop(#{port := Port} = State0) ->
- ?dbg({toerl_loop, Port, map_get(acc, State0),
- maps:get(match, State0, nomatch)}),
-
- State = handle_expect(State0),
-
- receive
- {Port,{data,Data}} when is_port(Port) ->
- ?dbg({?LINE,Port,{data,Data}}),
- toerl_loop(State#{acc => map_get(acc, State) ++ Data});
- {Pid, Ref, {expect, Expect, Timeout}} ->
- toerl_loop(init_expect(Pid, Ref, Expect, Timeout, State));
- {Pid, Ref, {send_data, Data}} ->
- Port ! {self(), {command, Data}},
- Pid ! {Ref, ok},
- toerl_loop(State);
- {_Pid, kill_emulator} ->
- kill_emulator(State);
- {timeout,Timer,expect_timeout} ->
- toerl_loop(handle_expect_timeout(Timer, State));
- {Port, eof} ->
- {error, unexpected_eof};
- Other ->
- {error, {unexpected, Other}}
- end.
-
-kill_emulator(#{spid := SPid, port := Port}) when is_pid(SPid) ->
- catch peer:stop(SPid),
- wait_for_eof(Port);
-kill_emulator(#{port := Port}) ->
- %% If the line happens to end in a ".", issuing "init:stop()."
- %% will result in a syntax error. To avoid that, issue a "\n"
- %% before "init:stop().".
- Port ! {self(),{command, "\ninit:stop().\n"}},
- wait_for_eof(Port).
-
-wait_for_eof(Port) ->
- receive
- {Port,eof} ->
- normal;
- _Other ->
- wait_for_eof(Port)
- after
- timeout(long) ->
- {error, kill_timeout}
- end.
-
-init_expect(Pid, Ref, ExpectList, Timeout, State) ->
- try compile_expect(ExpectList) of
- Expect ->
- Exp = #{expect => Expect,
- ref => Ref,
- source => ExpectList,
- timer => erlang:start_timer(Timeout, self(), expect_timeout),
- from => Pid},
- State#{expect => Exp}
- catch
- Class:Reason:Stk ->
- io:put_chars("Compilation of expect pattern failed:"),
- io:format("~p\n", [ExpectList]),
- io:put_chars(erl_error:format_exception(Class, Reason, Stk)),
- exit(expect_pattern_error)
- end.
-
-handle_expect(#{acc := Acc, expect := Exp} = State) ->
- #{expect := Expect, from := Pid, ref := Ref} = Exp,
- case Expect(Acc) of
- nomatch ->
- State;
- {matched, Eaten, Result} ->
- Pid ! {Ref, Result},
- finish_expect(Eaten, State)
- end;
-handle_expect(State) ->
- State.
-
-handle_expect_timeout(Timer, State) ->
- #{acc := Acc, expect := Exp} = State,
- #{expect := Expect, timer := Timer, from := Pid, ref := Ref} = Exp,
- case Expect({timeout, Acc}) of
- nomatch ->
- Result = {expect_timeout, Acc},
- Pid ! {Ref, Result},
- finish_expect(0, State);
- {matched, Eaten, Result} ->
- Pid ! {Ref, Result},
- finish_expect(Eaten, State)
- end.
-
-finish_expect(Eaten, #{acc := Acc0,
- expect := #{timer := Timer}}=State) ->
- erlang:cancel_timer(Timer),
- receive
- {timeout,Timer,timeout} ->
- ok
- after 0 ->
- ok
- end,
- Acc = lists:nthtail(Eaten, Acc0),
- maps:remove(expect, State#{acc := Acc}).
-
-compile_expect([{timeout,Action}|T]) when is_function(Action, 1) ->
- Next = compile_expect(T),
- fun({timeout, _}=Tm) ->
- {matched, 0, Action(Tm)};
- (Subject) ->
- Next(Subject)
- end;
-compile_expect([{{re,RE0},Action}|T]) when is_binary(RE0), is_function(Action, 1) ->
- {ok, RE} = re:compile(RE0),
- Next = compile_expect(T),
- fun({timeout, _}=Subject) ->
- Next(Subject);
- (Subject) ->
- case re:run(Subject, RE, [{capture,first,index}]) of
- nomatch ->
- Next(Subject);
- {match, [{Pos,Len}]} ->
- Matched = binary:part(list_to_binary(Subject), Pos, Len),
- {matched, Pos+Len, Action(Matched)}
- end
- end;
-compile_expect([RE|T]) when is_list(RE) ->
- Ok = fun(_) -> ok end,
- compile_expect([{{re,list_to_binary(RE)},Ok}|T]);
-compile_expect([]) ->
- fun(_) ->
- nomatch
- end.
-
-rtnode_check_logs(Logname, Pattern, Logs) ->
-rtnode_check_logs(Logname, Pattern, true, Logs).
-rtnode_check_logs(Logname, Pattern, Match, Logs) ->
- case re:run(maps:get(Logname, Logs), Pattern) of
- {match, [_]} when Match ->
- ok;
- nomatch when not Match ->
- ok;
- _ ->
- rtnode_dump_logs(Logs),
- ct:fail("~p not found in log ~ts",[Pattern, Logname])
- end.
-
-rtnode_dump_logs(Logs) ->
- maps:foreach(
- fun(File, Data) ->
- ct:pal("~ts: ~ts",[File, Data])
- end, Logs).
-
-rtnode_read_logs(Tempdir) ->
- {ok, LogFiles0} = file:list_dir(Tempdir),
-
- %% Make sure that we only read log files and not any named pipes.
- LogFiles = [F || F <- LogFiles0,
- case F of
- "erlang.log" ++ _ -> true;
- _ -> false
- end],
-
- lists:foldl(
- fun(File, Acc) ->
- case file:read_file(filename:join(Tempdir, File)) of
- {ok, Data} ->
- Acc#{ File => Data };
- _ ->
- Acc
- end
- end, #{}, LogFiles).
-
-get_default_shell() ->
- try
- rtnode([{putline,""},
- {putline, "is_pid(whereis(user_drv))."},
- {expect, "true\r\n"}]),
- new
- catch _E:_R ->
- ?dbg({_E,_R}),
- old
- end.
-
printed_atom(A) ->
lists:flatten(io_lib:format("~w", [A])).
diff --git a/lib/kernel/test/rtnode.erl b/lib/kernel/test/rtnode.erl
new file mode 100644
index 0000000000..af818557de
--- /dev/null
+++ b/lib/kernel/test/rtnode.erl
@@ -0,0 +1,538 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2009-2022. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%% http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(rtnode).
+
+-export([run/1, run/2, run/3, run/4, start/1, start/3, send_commands/3, stop/1,
+ start_runerl_command/3,
+ check_logs/3, check_logs/4, read_logs/1, dump_logs/1,
+ get_default_shell/0, get_progs/0, create_tempdir/0, timeout/1]).
+
+-include_lib("common_test/include/ct.hrl").
+
+%%-define(debug, true).
+
+-ifdef(debug).
+-define(dbg(Data),io:format(standard_error, "DBG: ~p\r\n",[Data])).
+-else.
+-define(dbg(Data),noop).
+-endif.
+
+-export([toerl_server/4]).
+
+%%
+%% Tool for running interactive shell, used by interactive_shell and io_proto SUITE
+%%
+run(C) ->
+ run(C, [], [], []).
+
+run(C, N) ->
+ run(C, N, [], []).
+
+run(Commands, Nodename, ErlPrefix) ->
+ run(Commands, Nodename, ErlPrefix, []).
+
+run(Commands, Nodename, ErlPrefix, Args) ->
+ case start(Nodename, ErlPrefix, Args) of
+ {ok, _SPid, CPid, RTState} ->
+ Res = catch send_commands(CPid, Commands, 1),
+ Logs = stop(RTState),
+ case Res of
+ ok ->
+ dump_logs(Logs),
+ ok;
+ _ ->
+ dump_logs(Logs),
+ ok = Res
+ end,
+ {ok, Logs};
+ Skip ->
+ Skip
+ end.
+
+start(Args) ->
+ start([], " ", Args).
+
+start(Nodename, ErlPrefix, Args) ->
+ case get_progs() of
+ {error,_Reason} ->
+ {skip,"No runerl present"};
+ {RunErl,ToErl,[Erl|ErlArgs] = ErlWArgs} ->
+ case create_tempdir() of
+ {error, Reason2} ->
+ {skip, Reason2};
+ Tempdir when ErlPrefix =/= [] ->
+ SPid =
+ start_runerl_node(RunErl,
+ ErlPrefix++"\\\""++Erl++"\\\" "++
+ lists:join($\s, ErlArgs),
+ Tempdir,Nodename,Args),
+ CPid = start_toerl_server(ToErl,Tempdir,undefined),
+ {ok, SPid, CPid, {CPid, SPid, ToErl, Tempdir}};
+ Tempdir ->
+ SPid = start_peer_runerl_node(RunErl,ErlWArgs,Tempdir,Nodename,Args),
+ CPid = start_toerl_server(ToErl,Tempdir,SPid),
+ {ok, SPid, CPid, {CPid, SPid, ToErl, Tempdir}}
+ end
+ end.
+
+stop({CPid, SPid, ToErl, Tempdir}) ->
+ %% Unlink from peer so that we don't crash when peer quits
+ unlink(SPid),
+ case stop_runerl_node(CPid) of
+ {error,_} ->
+ catch stop_try_harder(ToErl, Tempdir, SPid);
+ _ ->
+ ok
+ end,
+ wait_for_runerl_server(SPid),
+ Logs = read_logs(Tempdir),
+ file:del_dir_r(Tempdir),
+ Logs.
+
+stop_try_harder(ToErl, Tempdir, SPid) ->
+ CPid = start_toerl_server(ToErl, Tempdir, SPid),
+ ok = send_commands(CPid,
+ [{putline,[7]},
+ {expect, " --> $"},
+ {putline, "s"},
+ {putline, "c"},
+ {putline, ""}], 1),
+ stop_runerl_node(CPid).
+
+timeout(longest) ->
+ timeout(long) + timeout(normal);
+timeout(long) ->
+ 2 * timeout(normal);
+timeout(short) ->
+ timeout(normal) div 10;
+timeout(normal) ->
+ 10000 * test_server:timetrap_scale_factor().
+
+send_commands(CPid, [{sleep, X}|T], N) ->
+ ?dbg({sleep, X}),
+ receive
+ after X ->
+ send_commands(CPid, T, N+1)
+ end;
+send_commands(CPid, [{expect, Expect}|T], N) when is_list(Expect) ->
+ send_commands(CPid, [{expect, unicode, Expect}|T], N);
+send_commands(CPid, [{expect, Encoding, Expect}|T], N) when is_list(Expect) ->
+ ?dbg({expect, Expect}),
+ case command(CPid, {expect, Encoding, [Expect], timeout(normal)}) of
+ ok ->
+ send_commands(CPid, T, N + 1);
+ {expect_timeout, Got} ->
+ ct:pal("expect timed out waiting for ~p\ngot: ~p\n", [Expect,Got]),
+ {error, timeout};
+ Other ->
+ Other
+ end;
+send_commands(CPid, [{putline, Line}|T], N) ->
+ send_commands(CPid, [{putdata, Line ++ "\n"}|T], N);
+send_commands(CPid, [{putdata, Data}|T], N) ->
+ ?dbg({putdata, Data}),
+ case command(CPid, {send_data, Data}) of
+ ok ->
+ send_commands(CPid, T, N+1);
+ Error ->
+ Error
+ end;
+send_commands(_CPid, [], _) ->
+ ok.
+
+command(Pid, Req) ->
+ Timeout = timeout(longest),
+ Ref = erlang:monitor(process, Pid),
+ Pid ! {self(), Ref, Req},
+ receive
+ {Ref, Reply} ->
+ erlang:demonitor(Ref, [flush]),
+ Reply;
+ {'DOWN', Ref, _, _, Reason} ->
+ {error, Reason}
+ after Timeout ->
+ io:format("timeout while executing ~p\n", [Req]),
+ {error, timeout}
+ end.
+
+wait_for_runerl_server(SPid) ->
+ Ref = erlang:monitor(process, SPid),
+ Timeout = timeout(long),
+ receive
+ {'DOWN', Ref, process, SPid, _Reason} ->
+ ok
+ after Timeout ->
+ {error, runerl_server_timeout}
+ end.
+
+stop_runerl_node(CPid) ->
+ Ref = erlang:monitor(process, CPid),
+ CPid ! {self(), kill_emulator},
+ Timeout = timeout(longest),
+ receive
+ {'DOWN', Ref, process, CPid, noproc} ->
+ ok;
+ {'DOWN', Ref, process, CPid, normal} ->
+ ok;
+ {'DOWN', Ref, process, CPid, {error, Reason}} ->
+ {error, Reason}
+ after Timeout ->
+ {error, toerl_server_timeout}
+ end.
+
+get_progs() ->
+ case os:type() of
+ {unix,freebsd} ->
+ {error,"Can't use run_erl on FreeBSD"};
+ {unix,openbsd} ->
+ {error,"Can't use run_erl on OpenBSD"};
+ {unix,_} ->
+ RunErl = find_executable("run_erl"),
+ ToErl = find_executable("to_erl"),
+ Erl = string:split(ct:get_progname()," ",all),
+ {RunErl, ToErl, Erl};
+ _ ->
+ {error,"Not a Unix OS"}
+ end.
+
+find_executable(Name) ->
+ case os:find_executable(Name) of
+ Prog when is_list(Prog) ->
+ Prog;
+ false ->
+ throw("Could not find " ++ Name)
+ end.
+
+create_tempdir() ->
+ create_tempdir(filename:join(["/tmp","rtnode"++os:getpid()]),$A).
+
+create_tempdir(Dir,X) when X > $Z, X < $a ->
+ create_tempdir(Dir,$a);
+create_tempdir(Dir,X) when X > $z ->
+ Estr = lists:flatten(
+ io_lib:format("Unable to create ~s, reason eexist",
+ [Dir++[$z]])),
+ {error, Estr};
+create_tempdir(Dir0, Ch) ->
+ %% Expect fairly standard unix.
+ Dir = Dir0++[Ch],
+ case file:make_dir(Dir) of
+ {error, eexist} ->
+ create_tempdir(Dir0, Ch+1);
+ {error, Reason} ->
+ Estr = lists:flatten(
+ io_lib:format("Unable to create ~s, reason ~p",
+ [Dir,Reason])),
+ {error,Estr};
+ ok ->
+ Dir
+ end.
+
+start_runerl_node(RunErl,Erl,Tempdir,Nodename,Args) ->
+ XArg = case Nodename of
+ [] ->
+ [];
+ _ ->
+ " -sname "++(if is_atom(Nodename) -> atom_to_list(Nodename);
+ true -> Nodename
+ end)++
+ " -setcookie "++atom_to_list(erlang:get_cookie())
+ end ++ " " ++ Args,
+ spawn(fun() -> start_runerl_command(RunErl, Tempdir, Erl++XArg) end).
+
+start_runerl_command(RunErl, Tempdir, Cmd) ->
+ FullCmd = "\""++RunErl++"\" "++Tempdir++"/ "++Tempdir++" \""++Cmd++"\"",
+ ct:pal("~ts",[FullCmd]),
+ os:cmd(FullCmd).
+
+start_peer_runerl_node(RunErl,Erl,Tempdir,[],Args) ->
+ start_peer_runerl_node(RunErl,Erl,Tempdir,peer:random_name(),Args);
+start_peer_runerl_node(RunErl,Erl,Tempdir,Nodename,Args) ->
+ {ok, Peer, Node} =
+ ?CT_PEER(#{ name => Nodename,
+ exec => {RunErl,Erl},
+ detached => false,
+ shutdown => 10000,
+ post_process_args =>
+ fun(As) ->
+ [Tempdir++"/",Tempdir,
+ lists:flatten(
+ lists:join(
+ " ",[[$',A,$'] || A <- As]))]
+ end,
+ args => ["-connect_all","false"|Args] }),
+ Self = self(),
+ TraceLog = filename:join(Tempdir,Nodename++".trace"),
+ ct:pal("Link to trace: file://~ts",[TraceLog]),
+
+ spawn(Node,
+ fun() ->
+ try
+ %% {ok, _} = dbg:tracer(file, TraceLog),
+ %% dbg:p(whereis(user_drv),[c,m,timestamp]),
+ %% dbg:p(whereis(user_drv_reader),[c,m,timestamp]),
+ %% dbg:p(whereis(user_drv_writer),[c,m,timestamp]),
+ %% dbg:p(whereis(user),[c,m,timestamp]),
+ %% dbg:tp(user_drv,x),
+ %% dbg:tp(prim_tty,x),
+ %% dbg:tpl(prim_tty,read_nif,x),
+ Ref = monitor(process, Self),
+ receive {'DOWN',Ref,_,_,_} -> ok end
+ catch E:R:ST ->
+ io:format(user,"~p:~p:~p",[E,R,ST]),
+ erlang:raise(E,R,ST)
+ end
+ end),
+ Peer.
+
+start_toerl_server(ToErl,Tempdir,SPid) ->
+ Pid = spawn(?MODULE,toerl_server,[self(),ToErl,Tempdir,SPid]),
+ receive
+ {Pid,started} ->
+ Pid;
+ {Pid,error,Reason} ->
+ {error,Reason}
+ end.
+
+try_to_erl(_Command, 0) ->
+ {error, cannot_to_erl};
+try_to_erl(Command, N) ->
+ ?dbg({?LINE,N}),
+ Port = open_port({spawn, Command},[eof]),
+ Timeout = timeout(short) div 2,
+ receive
+ {Port, eof} ->
+ timer:sleep(Timeout),
+ try_to_erl(Command, N-1)
+ after Timeout ->
+ ?dbg(Port),
+ Port
+ end.
+
+toerl_server(Parent, ToErl, TempDir, SPid) ->
+ Port = try_to_erl("\""++ToErl++"\" "++TempDir++"/ 2>/dev/null", 8),
+ case Port of
+ P when is_port(P) ->
+ Parent ! {self(),started};
+ {error,Other} ->
+ Parent ! {self(),error,Other},
+ exit(Other)
+ end,
+
+ State = #{port => Port, acc => [], spid => SPid},
+ case toerl_loop(State) of
+ normal ->
+ ok;
+ {error, Reason} ->
+ error_logger:error_msg("toerl_server exit with reason ~p~n",
+ [Reason]),
+ exit(Reason)
+ end.
+
+toerl_loop(#{port := Port} = State0) ->
+ ?dbg({toerl_loop, Port, map_get(acc, State0),
+ maps:get(match, State0, nomatch)}),
+
+ State = handle_expect(State0),
+
+ receive
+ {Port,{data,Data}} when is_port(Port) ->
+ ?dbg({?LINE,Port,{data,Data}}),
+ toerl_loop(State#{acc => map_get(acc, State) ++ Data});
+ {Pid, Ref, {expect, Encoding, Expect, Timeout}} ->
+ toerl_loop(init_expect(Pid, Ref, Encoding, Expect, Timeout, State));
+ {Pid, Ref, {send_data, Data}} ->
+ ?dbg({?LINE,Port,{send_data,Data}}),
+ Port ! {self(), {command, Data}},
+ Pid ! {Ref, ok},
+ toerl_loop(State);
+ {_Pid, kill_emulator} ->
+ kill_emulator(State);
+ {timeout,Timer,expect_timeout} ->
+ toerl_loop(handle_expect_timeout(Timer, State));
+ {Port, eof} ->
+ {error, unexpected_eof};
+ Other ->
+ {error, {unexpected, Other}}
+ end.
+
+kill_emulator(#{spid := SPid, port := Port}) when is_pid(SPid) ->
+ catch peer:stop(SPid),
+ wait_for_eof(Port);
+kill_emulator(#{port := Port}) ->
+ %% If the line happens to end in a ".", issuing "init:stop()."
+ %% will result in a syntax error. To avoid that, issue a "\n"
+ %% before "init:stop().".
+ Port ! {self(),{command, "\ninit:stop().\n"}},
+ wait_for_eof(Port).
+
+wait_for_eof(Port) ->
+ receive
+ {Port,eof} ->
+ normal;
+ _Other ->
+ wait_for_eof(Port)
+ after
+ timeout(long) ->
+ {error, kill_timeout}
+ end.
+
+init_expect(Pid, Ref, Encoding, ExpectList, Timeout, State) ->
+ try compile_expect(ExpectList, Encoding) of
+ Expect ->
+ Exp = #{expect => Expect,
+ ref => Ref,
+ source => ExpectList,
+ timer => erlang:start_timer(Timeout, self(), expect_timeout),
+ from => Pid},
+ State#{expect => Exp}
+ catch
+ Class:Reason:Stk ->
+ io:put_chars("Compilation of expect pattern failed:"),
+ io:format("~p\n", [ExpectList]),
+ io:put_chars(erl_error:format_exception(Class, Reason, Stk)),
+ exit(expect_pattern_error)
+ end.
+
+handle_expect(#{acc := Acc, expect := Exp} = State) ->
+ #{expect := Expect, from := Pid, ref := Ref} = Exp,
+ case Expect(Acc) of
+ nomatch ->
+ State;
+ {matched, Eaten, Result} ->
+ Pid ! {Ref, Result},
+ finish_expect(Eaten, State)
+ end;
+handle_expect(State) ->
+ State.
+
+handle_expect_timeout(Timer, State) ->
+ #{acc := Acc, expect := Exp} = State,
+ #{expect := Expect, timer := Timer, from := Pid, ref := Ref} = Exp,
+ case Expect({timeout, Acc}) of
+ nomatch ->
+ Result = {expect_timeout, Acc},
+ Pid ! {Ref, Result},
+ finish_expect(0, State);
+ {matched, Eaten, Result} ->
+ Pid ! {Ref, Result},
+ finish_expect(Eaten, State)
+ end.
+
+finish_expect(Eaten, #{acc := Acc0,
+ expect := #{timer := Timer}}=State) ->
+ erlang:cancel_timer(Timer),
+ receive
+ {timeout,Timer,timeout} ->
+ ok
+ after 0 ->
+ ok
+ end,
+ Acc = lists:nthtail(Eaten, Acc0),
+ maps:remove(expect, State#{acc := Acc}).
+
+compile_expect([{timeout,Action}|T], E) when is_function(Action, 1) ->
+ Next = compile_expect(T, E),
+ fun({timeout, _}=Tm) ->
+ {matched, 0, Action(Tm)};
+ (Subject) ->
+ Next(Subject)
+ end;
+compile_expect([{{re,RE0},Action}|T], E) when is_binary(RE0), is_function(Action, 1) ->
+ {ok, RE} = re:compile(RE0, [unicode || E =:= unicode]),
+ Next = compile_expect(T, E),
+ fun({timeout, _}=Subject) ->
+ Next(Subject);
+ (Subject) ->
+ BinarySubject = if
+ E =:= unicode ->
+ unicode:characters_to_binary(list_to_binary(Subject));
+ E =:= latin1 ->
+ list_to_binary(Subject)
+ end,
+ case re:run(BinarySubject, RE, [{capture,first,index}]) of
+ nomatch ->
+ Next(Subject);
+ {match, [{Pos,Len}]} ->
+ Matched = binary:part(BinarySubject, Pos, Len),
+ {matched, Pos+Len, Action(Matched)}
+ end
+ end;
+compile_expect([RE|T], E) when is_list(RE) ->
+ Ok = fun(_) -> ok end,
+ compile_expect([{{re,unicode:characters_to_binary(RE, unicode, E)},Ok}|T], E);
+compile_expect([], _E) ->
+ fun(_) ->
+ nomatch
+ end.
+
+check_logs(Logname, Pattern, Logs) ->
+check_logs(Logname, Pattern, true, Logs).
+check_logs(Logname, Pattern, Match, Logs) ->
+ case re:run(maps:get(Logname, Logs), Pattern) of
+ {match, [_]} when Match ->
+ ok;
+ nomatch when not Match ->
+ ok;
+ _ ->
+ dump_logs(Logs),
+ ct:fail("~p not found in log ~ts",[Pattern, Logname])
+ end.
+
+dump_logs(Logs) ->
+ maps:foreach(
+ fun(File, Data) ->
+ ct:pal("~ts: ~ts",[File, Data])
+ end, Logs).
+
+read_logs(Tempdir) ->
+ {ok, LogFiles0} = file:list_dir(Tempdir),
+
+ %% Make sure that we only read log files and not any named pipes.
+ LogFiles = [F || F <- LogFiles0,
+ case F of
+ "erlang.log" ++ _ -> true;
+ _ -> false
+ end],
+
+ lists:foldl(
+ fun(File, Acc) ->
+ case file:read_file(filename:join(Tempdir, File)) of
+ {ok, Data} ->
+ Acc#{ File => Data };
+ _ ->
+ Acc
+ end
+ end, #{}, LogFiles).
+
+get_default_shell() ->
+ case get_progs() of
+ {error,_} ->
+ noshell;
+ _ ->
+ try
+ run([{putline,""},
+ {putline, "is_pid(whereis(user_drv))."},
+ {expect, "true\r\n"}]),
+ new
+ catch _E:_R ->
+ old
+ end
+ end.
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile
index 9ccd48bcc7..0ee9ee6f6d 100644
--- a/lib/stdlib/test/Makefile
+++ b/lib/stdlib/test/Makefile
@@ -105,10 +105,12 @@ MODULES= \
ERTS_MODULES= erts_test_utils
SASL_MODULES= otp_vsns
+KERNEL_MODULES= rtnode
ERL_FILES= $(MODULES:%=%.erl) \
$(ERTS_MODULES:%=$(ERL_TOP)/erts/emulator/test/%.erl) \
- $(SASL_MODULES:%=$(ERL_TOP)/lib/sasl/test/%.erl)
+ $(SASL_MODULES:%=$(ERL_TOP)/lib/sasl/test/%.erl) \
+ $(KERNEL_MODULES:%=$(ERL_TOP)/lib/kernel/test/%.erl)
EXTRA_FILES= $(ERL_TOP)/otp_versions.table
@@ -136,7 +138,7 @@ COVERFILE=stdlib.cover
make_emakefile:
$(ERL_TOP)/make/make_emakefile $(ERL_COMPILE_FLAGS) -o$(EBIN) \
- $(MODULES) $(ERTS_MODULES) $(SASL_MODULES) \
+ $(MODULES) $(ERTS_MODULES) $(SASL_MODULES) $(KERNEL_MODULES) \
> $(EMAKEFILE)
tests $(TYPES): make_emakefile
diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl
index b7568203fd..482e233493 100644
--- a/lib/stdlib/test/io_proto_SUITE.erl
+++ b/lib/stdlib/test/io_proto_SUITE.erl
@@ -22,8 +22,6 @@
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
init_per_group/2,end_per_group/2]).
--export([init_per_testcase/2, end_per_testcase/2]).
-
-export([setopts_getopts/1,unicode_options/1,unicode_options_gen/1,
binary_options/1, read_modes_gl/1,
read_modes_ogl/1, broken_unicode/1,eof_on_pipe/1,unicode_prompt/1]).
@@ -32,35 +30,18 @@
-export([io_server_proxy/1,start_io_server_proxy/0, proxy_getall/1,
proxy_setnext/2, proxy_quit/1]).
%% For spawn
--export([toerl_server/4,answering_machine1/3,answering_machine2/3]).
+-export([answering_machine1/3, answering_machine2/3]).
-export([uprompt/1]).
--include_lib("common_test/include/ct.hrl").
--define(privdir(Conf), proplists:get_value(priv_dir, Conf)).
-
%%-define(debug, true).
-ifdef(debug).
--define(format(S, A), io:format(S, A)).
-define(dbg(Data),io:format(standard_error, "DBG: ~p\r\n",[Data])).
--define(RM_RF(Dir),begin io:format(standard_error, "Not Removed: ~p\r\n",[Dir]),
- ok end).
-else.
--define(format(S, A), ok).
-define(dbg(Data),noop).
--define(RM_RF(Dir),rm_rf(Dir)).
-endif.
-init_per_testcase(_Case, Config) ->
- Term = os:getenv("TERM", "dumb"),
- os:putenv("TERM","vt100"),
- [{term, Term} | Config].
-end_per_testcase(_Case, Config) ->
- Term = proplists:get_value(term,Config),
- os:putenv("TERM",Term),
- ok.
-
suite() ->
[{ct_hooks,[ts_install_cth]},
{timetrap,{minutes,5}}].
@@ -74,10 +55,14 @@ groups() ->
[].
init_per_suite(Config) ->
- DefShell = get_default_shell(),
- [{default_shell,DefShell}|Config].
+ Term = os:getenv("TERM", "dumb"),
+ os:putenv("TERM","vt100"),
+ DefShell = rtnode:get_default_shell(),
+ [{default_shell,DefShell},{term, Term}|Config].
-end_per_suite(_Config) ->
+end_per_suite(Config) ->
+ Term = proplists:get_value(term,Config),
+ os:putenv("TERM",Term),
ok.
init_per_group(_GroupName, Config) ->
@@ -86,13 +71,11 @@ init_per_group(_GroupName, Config) ->
end_per_group(_GroupName, Config) ->
Config.
-
-
-record(state, {
- q = [],
- nxt = eof,
- mode = list
- }).
+ q = [],
+ nxt = eof,
+ mode = list
+ }).
uprompt(_L) ->
[1050,1072,1082,1074,1086,32,1077,32,85,110,105,99,111,100,101,32,63].
@@ -101,10 +84,8 @@ uprompt(_L) ->
unicode_prompt(Config) when is_list(Config) ->
PA = filename:dirname(code:which(?MODULE)),
case proplists:get_value(default_shell,Config) of
- old ->
- ok;
new ->
- rtnode(
+ rtnode:run(
[{putline,""},
{putline, "2."},
{expect, "[\n ]2"},
@@ -124,7 +105,7 @@ unicode_prompt(Config) when is_list(Config) ->
ok
end,
%% And one with oldshell
- rtnode(
+ rtnode:run(
[{putline,""},
{putline, "2."},
{expect, "[\n ]2"},
@@ -218,11 +199,9 @@ setopts_getopts(Config) when is_list(Config) ->
eof = io:get_line(RFile,''),
file:close(RFile),
case proplists:get_value(default_shell,Config) of
- old ->
- ok;
new ->
%% So, lets test another node with new interactive shell
- rtnode(
+ rtnode:run(
[{putline,""},
{putline, "2."},
{expect, "[\n ]2[^.]"},
@@ -241,7 +220,7 @@ setopts_getopts(Config) when is_list(Config) ->
ok
end,
%% And one with oldshell
- rtnode(
+ rtnode:run(
[{putline,""},
{putline, "2."},
{expect, "[\n ]2[^.]"},
@@ -419,11 +398,9 @@ unicode_options(Config) when is_list(Config) ->
[ ok = CannotWriteFile(F,FailDir) || F <- AllNoBom ],
case proplists:get_value(default_shell,Config) of
- old ->
- ok;
new ->
%% OK, time for the group_leaders...
- rtnode(
+ rtnode:run(
[{putline,""},
{putline, "2."},
{expect, "[\n ]2[^.]"},
@@ -439,7 +416,7 @@ unicode_options(Config) when is_list(Config) ->
_ ->
ok
end,
- rtnode(
+ rtnode:run(
[{putline,""},
{putline, "2."},
{expect, "[\n ]2[^.]"},
@@ -707,10 +684,8 @@ binary_options(Config) when is_list(Config) ->
%% OK, time for the group_leaders...
case proplists:get_value(default_shell,Config) of
- old ->
- ok;
new ->
- rtnode(
+ rtnode:run(
[{putline, "2."},
{expect, "[\n ]2[^.]"},
{putline, "lists:keyfind(binary,1,io:getopts())."},
@@ -731,7 +706,7 @@ binary_options(Config) when is_list(Config) ->
ok
end,
%% And one with oldshell
- rtnode(
+ rtnode:run(
[{putline, "2."},
{expect, "[\n ]2[^.]"},
{putline, "lists:keyfind(binary,1,io:getopts())."},
@@ -750,78 +725,83 @@ binary_options(Config) when is_list(Config) ->
],[],"",["-oldshell"]),
ok.
-
-
-
answering_machine1(OthNode,OthReg,Me) ->
TestDataLine1 = [229,228,246],
TestDataUtf = binary_to_list(unicode:characters_to_binary(TestDataLine1)),
- rtnode([{putline,""},
- {putline, "2."},
- {expect, "2"},
- {putline, "io:getopts()."},
- {expect, ">"},
- {putline, "{"++OthReg++","++OthNode++"} ! group_leader()."},
- {expect, "<"},
- %% get_line
- {expect, ".*Prompt"},
- {putline, "Hej"},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, "Hej"},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataLine1},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataLine1},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataUtf},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataUtf},
- {expect, ".*Okej"},
- %% get_chars
- {expect, ".*Prompt"},
- {putline, "Hej"},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, "Hej"},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataLine1},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataLine1},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataUtf},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataUtf},
- {expect, ".*Okej"},
- %% fread
- {expect, ".*Prompt"},
- {putline, "Hej"},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, "Hej"},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataLine1},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataLine1},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataUtf},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataUtf},
- {expect, ".*Okej"}
-
- ],Me,"",["-env","LC_ALL",get_lc_ctype()]),
+ TestDataLine1Oct = "\\\\345( \b)*\\\\344( \b)*\\\\366",
+ rtnode:run(
+ [{putline,""},
+ {putline, "2."},
+ {expect, "2"},
+ {putline, "io:getopts()."},
+ {expect, ">"},
+ {putline, "{"++OthReg++","++OthNode++"} ! group_leader()."},
+ {expect, "<"},
+ %% get_line
+ {expect, "Prompt"},
+ {putline, "Hej"},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, "Hej"},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataLine1},
+ {expect, latin1, "\n" ++ TestDataLine1Oct},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataLine1},
+ {expect, latin1, "\n" ++ TestDataLine1Oct},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataUtf},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataUtf},
+ {expect, "Okej"},
+ %% get_chars
+ {expect, "Prompt"},
+ {putline, "Hej"},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, "Hej"},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataLine1},
+ {expect, latin1, "\n" ++ TestDataLine1Oct},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataLine1},
+ {expect, latin1, "\n" ++ TestDataLine1Oct},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataUtf},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataUtf},
+ {expect, "Okej"},
+ %% fread
+ {expect, "Prompt"},
+ {putline, "Hej"},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, "Hej"},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataLine1},
+ {expect, latin1, "\n" ++ TestDataLine1Oct},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataLine1},
+ {expect, latin1, "\n" ++ TestDataLine1Oct},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataUtf},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataUtf},
+ {expect, "Okej"}
+
+ ],Me,"",["-env","LC_ALL",get_lc_ctype()]),
O = list_to_atom(OthReg),
O ! {self(),done},
ok.
@@ -829,70 +809,77 @@ answering_machine1(OthNode,OthReg,Me) ->
answering_machine2(OthNode,OthReg,Me) ->
TestDataLine1 = [229,228,246],
TestDataUtf = binary_to_list(unicode:characters_to_binary(TestDataLine1)),
- rtnode([{putline,""},
- {putline, "2."},
- {expect, "2"},
- {putline, "{"++OthReg++","++OthNode++"} ! group_leader()."},
- {expect, ".*<[0-9].*"},
- %% get_line
- {expect, ".*Prompt"},
- {putline, "Hej"},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, "Hej"},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataLine1},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataLine1},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataUtf},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataUtf},
- {expect, ".*Okej"},
- %% get_chars
- {expect, ".*Prompt"},
- {putline, "Hej"},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, "Hej"},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataLine1},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataLine1},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataUtf},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataUtf},
- {expect, ".*Okej"},
- %% fread
- {expect, ".*Prompt"},
- {putline, "Hej"},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, "Hej"},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataLine1},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataLine1},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataUtf},
- {expect, ".*Okej"},
- {expect, ".*Prompt"},
- {putline, TestDataUtf},
- {expect, ".*Okej"}
-
- ],Me,"",["-oldshell","-env","LC_ALL",get_lc_ctype()]),
+ rtnode:run(
+ [{putline,""},
+ {putline, "2."},
+ {expect, "2"},
+ {putline, "{"++OthReg++","++OthNode++"} ! group_leader()."},
+ {expect, "<[0-9].*"},
+ %% get_line
+ {expect, "Prompt"},
+ {putline, "Hej"},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, "Hej"},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataLine1},
+ {expect, latin1, "\n" ++ TestDataLine1},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataLine1},
+ {expect, latin1, "\n" ++ TestDataLine1},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataUtf},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataUtf},
+ {expect, "Okej"},
+ %% get_chars
+ {expect, "Prompt"},
+ {putline, "Hej"},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, "Hej"},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataLine1},
+ {expect, latin1, "\n" ++ TestDataLine1},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataLine1},
+ {expect, latin1, "\n" ++ TestDataLine1},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataUtf},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataUtf},
+ {expect, "Okej"},
+ %% fread
+ {expect, "Prompt"},
+ {putline, "Hej"},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, "Hej"},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataLine1},
+ {expect, latin1, "\n" ++ TestDataLine1},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataLine1},
+ {expect, latin1, "\n" ++ TestDataLine1},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataUtf},
+ {expect, "Okej"},
+ {expect, "Prompt"},
+ {putline, TestDataUtf},
+ {expect, "Okej"}
+
+ ],Me,"",["-oldshell","-env","LC_ALL",get_lc_ctype()]),
O = list_to_atom(OthReg),
O ! {self(),done},
ok.
@@ -900,19 +887,19 @@ answering_machine2(OthNode,OthReg,Me) ->
%% Test various modes when reading from the group leade from another machine.
read_modes_ogl(Config) when is_list(Config) ->
- case get_progs() of
- {error,Reason} ->
- {skipped,Reason};
+ case proplists:get_value(default_shell,Config) of
+ noshell ->
+ {skipped,"No run_erl"};
_ ->
read_modes_gl_1(Config,answering_machine2)
end.
%% Test various modes when reading from the group leade from another machine.
read_modes_gl(Config) when is_list(Config) ->
- case {get_progs(),proplists:get_value(default_shell,Config)} of
- {{error,Reason},_} ->
- {skipped,Reason};
- {_,old} ->
+ case proplists:get_value(default_shell,Config) of
+ noshell ->
+ {skipped,"No run_erl"};
+ old ->
{skipped,"No new shell"};
_ ->
read_modes_gl_1(Config,answering_machine1)
@@ -1027,14 +1014,10 @@ loop_through_file2(_,{error,_Err},_,_) ->
loop_through_file2(F,Bin,Chunk,Enc) when is_binary(Bin) ->
loop_through_file2(F,io:get_chars(F,'',Chunk),Chunk,Enc).
-
-
%% Test eof before newline on stdin when erlang is in pipe.
eof_on_pipe(Config) when is_list(Config) ->
- case {get_progs(),os:type()} of
- {{error,Reason},_} ->
- {skipped,Reason};
- {{_,_,Erl},{unix,linux}} ->
+ case {ct:get_progname(),os:type()} of
+ {Erl,{unix,linux}} ->
%% Not even Linux is reliable - echo can be both styles
try
EchoLine = case os:cmd("echo -ne \"test\\ntest\"") of
@@ -1078,497 +1061,6 @@ eof_on_pipe(Config) when is_list(Config) ->
{skipped,"Only on linux"}
end.
-
-%%
-%% Tool for running interactive shell (stolen from the kernel
-%% test suite interactive_shell_SUITE)
-%%
-rtnode(C) ->
- rtnode(C, [], [], []).
-
-rtnode(C, N) ->
- rtnode(C, N, [], []).
-
-rtnode(Commands, Nodename, ErlPrefix) ->
- rtnode(Commands, Nodename, ErlPrefix, []).
-
-rtnode(Commands, Nodename, ErlPrefix, Args) ->
- case rtstart(Nodename, ErlPrefix, Args) of
- {ok, _SPid, CPid, RTState} ->
- Res = catch send_commands(CPid, Commands, 1),
- Logs = rtstop(RTState),
- case Res of
- ok ->
- rtnode_dump_logs(Logs),
- ok;
- _ ->
- rtnode_dump_logs(Logs),
- ok = Res
- end,
- {ok, Logs};
- Skip ->
- Skip
- end.
-
-rtstart(Args) ->
- rtstart([], " ", Args).
-
-rtstart(Nodename, ErlPrefix, Args) ->
- case get_progs() of
- {error,_Reason} ->
- {skip,"No runerl present"};
- {RunErl,ToErl,[Erl|ErlArgs] = ErlWArgs} ->
- case create_tempdir() of
- {error, Reason2} ->
- {skip, Reason2};
- Tempdir when ErlPrefix =/= [] ->
- SPid =
- start_runerl_node(RunErl,
- ErlPrefix++"\\\""++Erl++"\\\" "++
- lists:join($\s, ErlArgs),
- Tempdir,Nodename,Args),
- CPid = start_toerl_server(ToErl,Tempdir,undefined),
- {ok, SPid, CPid, {CPid, SPid, ToErl, Tempdir}};
- Tempdir ->
- SPid = start_peer_runerl_node(RunErl,ErlWArgs,Tempdir,Nodename,Args),
- CPid = start_toerl_server(ToErl,Tempdir,SPid),
- {ok, SPid, CPid, {CPid, SPid, ToErl, Tempdir}}
- end
- end.
-
-rtstop({CPid, SPid, ToErl, Tempdir}) ->
- %% Unlink from peer so that we don't crash when peer quits
- unlink(SPid),
- case stop_runerl_node(CPid) of
- {error,_} ->
- catch rtstop_try_harder(ToErl, Tempdir, SPid);
- _ ->
- ok
- end,
- wait_for_runerl_server(SPid),
- Logs = rtnode_read_logs(Tempdir),
-% file:del_dir_r(Tempdir),
- Logs.
-
-rtstop_try_harder(ToErl, Tempdir, SPid) ->
- CPid = start_toerl_server(ToErl, Tempdir, SPid),
- ok = send_commands(CPid,
- [{putline,[7]},
- {expect, " --> $"},
- {putline, "s"},
- {putline, "c"},
- {putline, ""}], 1),
- stop_runerl_node(CPid).
-
-timeout(longest) ->
- timeout(long) + timeout(normal);
-timeout(long) ->
- 2 * timeout(normal);
-timeout(short) ->
- timeout(normal) div 10;
-timeout(normal) ->
- 10000 * test_server:timetrap_scale_factor().
-
-send_commands(CPid, [{sleep, X}|T], N) ->
- ?dbg({sleep, X}),
- receive
- after X ->
- send_commands(CPid, T, N+1)
- end;
-send_commands(CPid, [{expect, Expect}|T], N) when is_list(Expect) ->
- ?dbg({expect, Expect}),
- case command(CPid, {expect, [Expect], timeout(normal)}) of
- ok ->
- send_commands(CPid, T, N + 1);
- {expect_timeout, Got} ->
- ct:pal("expect timed out waiting for ~p\ngot: ~p\n", [Expect,Got]),
- {error, timeout};
- Other ->
- Other
- end;
-send_commands(CPid, [{putline, Line}|T], N) ->
- send_commands(CPid, [{putdata, Line ++ "\n"}|T], N);
-send_commands(CPid, [{putdata, Data}|T], N) ->
- ?dbg({putdata, Data}),
- case command(CPid, {send_data, Data}) of
- ok ->
- send_commands(CPid, T, N+1);
- Error ->
- Error
- end;
-send_commands(_CPid, [], _) ->
- ok.
-
-command(Pid, Req) ->
- Timeout = timeout(longest),
- Ref = erlang:monitor(process, Pid),
- Pid ! {self(), Ref, Req},
- receive
- {Ref, Reply} ->
- erlang:demonitor(Ref, [flush]),
- Reply;
- {'DOWN', Ref, _, _, Reason} ->
- {error, Reason}
- after Timeout ->
- io:format("timeout while executing ~p\n", [Req]),
- {error, timeout}
- end.
-
-wait_for_runerl_server(SPid) ->
- Ref = erlang:monitor(process, SPid),
- Timeout = timeout(long),
- receive
- {'DOWN', Ref, process, SPid, _Reason} ->
- ok
- after Timeout ->
- {error, runerl_server_timeout}
- end.
-
-stop_runerl_node(CPid) ->
- Ref = erlang:monitor(process, CPid),
- CPid ! {self(), kill_emulator},
- Timeout = timeout(longest),
- receive
- {'DOWN', Ref, process, CPid, noproc} ->
- ok;
- {'DOWN', Ref, process, CPid, normal} ->
- ok;
- {'DOWN', Ref, process, CPid, {error, Reason}} ->
- {error, Reason}
- after Timeout ->
- {error, toerl_server_timeout}
- end.
-
-get_progs() ->
- case os:type() of
- {unix,freebsd} ->
- {error,"Can't use run_erl on FreeBSD"};
- {unix,openbsd} ->
- {error,"Can't use run_erl on OpenBSD"};
- {unix,_} ->
- RunErl = find_executable("run_erl"),
- ToErl = find_executable("to_erl"),
- Erl = string:split(ct:get_progname()," ",all),
- {RunErl, ToErl, Erl};
- _ ->
- {error,"Not a Unix OS"}
- end.
-
-find_executable(Name) ->
- case os:find_executable(Name) of
- Prog when is_list(Prog) ->
- Prog;
- false ->
- throw("Could not find " ++ Name)
- end.
-
-create_tempdir() ->
- create_tempdir(filename:join(["/tmp","rtnode"++os:getpid()]),$A).
-
-create_tempdir(Dir,X) when X > $Z, X < $a ->
- create_tempdir(Dir,$a);
-create_tempdir(Dir,X) when X > $z ->
- Estr = lists:flatten(
- io_lib:format("Unable to create ~s, reason eexist",
- [Dir++[$z]])),
- {error, Estr};
-create_tempdir(Dir0, Ch) ->
- %% Expect fairly standard unix.
- Dir = Dir0++[Ch],
- case file:make_dir(Dir) of
- {error, eexist} ->
- create_tempdir(Dir0, Ch+1);
- {error, Reason} ->
- Estr = lists:flatten(
- io_lib:format("Unable to create ~s, reason ~p",
- [Dir,Reason])),
- {error,Estr};
- ok ->
- Dir
- end.
-
-start_runerl_node(RunErl,Erl,Tempdir,Nodename,Args) ->
- XArg = case Nodename of
- [] ->
- [];
- _ ->
- " -sname "++(if is_atom(Nodename) -> atom_to_list(Nodename);
- true -> Nodename
- end)++
- " -setcookie "++atom_to_list(erlang:get_cookie())
- end ++ " " ++ Args,
- spawn(fun() -> start_runerl_command(RunErl, Tempdir, Erl++XArg) end).
-
-start_runerl_command(RunErl, Tempdir, Cmd) ->
- FullCmd = "\""++RunErl++"\" "++Tempdir++"/ "++Tempdir++" \""++Cmd++"\"",
- ct:pal("~ts",[FullCmd]),
- os:cmd(FullCmd).
-
-start_peer_runerl_node(RunErl,Erl,Tempdir,[],Args) ->
- start_peer_runerl_node(RunErl,Erl,Tempdir,peer:random_name(),Args);
-start_peer_runerl_node(RunErl,Erl,Tempdir,Nodename,Args) ->
- {ok, Peer, Node} =
- ?CT_PEER(#{ name => Nodename,
- exec => {RunErl,Erl},
- detached => false,
- shutdown => 10000,
- post_process_args =>
- fun(As) ->
- [Tempdir++"/",Tempdir,
- lists:flatten(
- lists:join(
- " ",[[$',A,$'] || A <- As]))]
- end,
- args => ["-connect_all","false"|Args] }),
- Self = self(),
- TraceLog = filename:join(Tempdir,Nodename++".trace"),
- ct:pal("Link to trace: file://~ts",[TraceLog]),
-
- spawn(Node,
- fun() ->
- try
- %% {ok, _} = dbg:tracer(file, TraceLog),
- %% dbg:p(whereis(user_drv),[c,m,timestamp]),
- %% dbg:p(whereis(user_drv_reader),[c,m,timestamp]),
- %% dbg:p(whereis(user_drv_writer),[c,m,timestamp]),
- %% dbg:p(whereis(user),[c,m,timestamp]),
- %% dbg:tp(user_drv,x),
- %% dbg:tp(prim_tty,x),
- %% dbg:tpl(prim_tty,read_nif,x),
- Ref = monitor(process, Self),
- receive {'DOWN',Ref,_,_,_} -> ok end
- catch E:R:ST ->
- io:format(user,"~p:~p:~p",[E,R,ST]),
- erlang:raise(E,R,ST)
- end
- end),
- Peer.
-
-start_toerl_server(ToErl,Tempdir,SPid) ->
- Pid = spawn(?MODULE,toerl_server,[self(),ToErl,Tempdir,SPid]),
- receive
- {Pid,started} ->
- Pid;
- {Pid,error,Reason} ->
- {error,Reason}
- end.
-
-try_to_erl(_Command, 0) ->
- {error, cannot_to_erl};
-try_to_erl(Command, N) ->
- ?dbg({?LINE,N}),
- Port = open_port({spawn, Command},[eof]),
- Timeout = timeout(short) div 2,
- receive
- {Port, eof} ->
- timer:sleep(Timeout),
- try_to_erl(Command, N-1)
- after Timeout ->
- ?dbg(Port),
- Port
- end.
-
-toerl_server(Parent, ToErl, TempDir, SPid) ->
- Port = try_to_erl("\""++ToErl++"\" "++TempDir++"/ 2>/dev/null", 8),
- case Port of
- P when is_port(P) ->
- Parent ! {self(),started};
- {error,Other} ->
- Parent ! {self(),error,Other},
- exit(Other)
- end,
-
- State = #{port => Port, acc => [], spid => SPid},
- case toerl_loop(State) of
- normal ->
- ok;
- {error, Reason} ->
- error_logger:error_msg("toerl_server exit with reason ~p~n",
- [Reason]),
- exit(Reason)
- end.
-
-toerl_loop(#{port := Port} = State0) ->
- ?dbg({toerl_loop, Port, map_get(acc, State0),
- maps:get(match, State0, nomatch)}),
-
- State = handle_expect(State0),
-
- receive
- {Port,{data,Data}} when is_port(Port) ->
- ?dbg({?LINE,Port,{data,Data}}),
- toerl_loop(State#{acc => map_get(acc, State) ++ Data});
- {Pid, Ref, {expect, Expect, Timeout}} ->
- toerl_loop(init_expect(Pid, Ref, Expect, Timeout, State));
- {Pid, Ref, {send_data, Data}} ->
- ?dbg({?LINE,Port,{send_data,Data}}),
- Port ! {self(), {command, Data}},
- Pid ! {Ref, ok},
- toerl_loop(State);
- {_Pid, kill_emulator} ->
- kill_emulator(State);
- {timeout,Timer,expect_timeout} ->
- toerl_loop(handle_expect_timeout(Timer, State));
- {Port, eof} ->
- {error, unexpected_eof};
- Other ->
- {error, {unexpected, Other}}
- end.
-
-kill_emulator(#{spid := SPid, port := Port}) when is_pid(SPid) ->
- catch peer:stop(SPid),
- wait_for_eof(Port);
-kill_emulator(#{port := Port}) ->
- %% If the line happens to end in a ".", issuing "init:stop()."
- %% will result in a syntax error. To avoid that, issue a "\n"
- %% before "init:stop().".
- Port ! {self(),{command, "\ninit:stop().\n"}},
- wait_for_eof(Port).
-
-wait_for_eof(Port) ->
- receive
- {Port,eof} ->
- normal;
- _Other ->
- wait_for_eof(Port)
- after
- timeout(long) ->
- {error, kill_timeout}
- end.
-
-init_expect(Pid, Ref, ExpectList, Timeout, State) ->
- try compile_expect(ExpectList) of
- Expect ->
- Exp = #{expect => Expect,
- ref => Ref,
- source => ExpectList,
- timer => erlang:start_timer(Timeout, self(), expect_timeout),
- from => Pid},
- State#{expect => Exp}
- catch
- Class:Reason:Stk ->
- io:put_chars("Compilation of expect pattern failed:"),
- io:format("~p\n", [ExpectList]),
- io:put_chars(erl_error:format_exception(Class, Reason, Stk)),
- exit(expect_pattern_error)
- end.
-
-handle_expect(#{acc := Acc, expect := Exp} = State) ->
- #{expect := Expect, from := Pid, ref := Ref} = Exp,
- case Expect(Acc) of
- nomatch ->
- State;
- {matched, Eaten, Result} ->
- Pid ! {Ref, Result},
- finish_expect(Eaten, State)
- end;
-handle_expect(State) ->
- State.
-
-handle_expect_timeout(Timer, State) ->
- #{acc := Acc, expect := Exp} = State,
- #{expect := Expect, timer := Timer, from := Pid, ref := Ref} = Exp,
- case Expect({timeout, Acc}) of
- nomatch ->
- Result = {expect_timeout, Acc},
- Pid ! {Ref, Result},
- finish_expect(0, State);
- {matched, Eaten, Result} ->
- Pid ! {Ref, Result},
- finish_expect(Eaten, State)
- end.
-
-finish_expect(Eaten, #{acc := Acc0,
- expect := #{timer := Timer}}=State) ->
- erlang:cancel_timer(Timer),
- receive
- {timeout,Timer,timeout} ->
- ok
- after 0 ->
- ok
- end,
- Acc = lists:nthtail(Eaten, Acc0),
- maps:remove(expect, State#{acc := Acc}).
-
-compile_expect([{timeout,Action}|T]) when is_function(Action, 1) ->
- Next = compile_expect(T),
- fun({timeout, _}=Tm) ->
- {matched, 0, Action(Tm)};
- (Subject) ->
- Next(Subject)
- end;
-compile_expect([{{re,RE0},Action}|T]) when is_binary(RE0), is_function(Action, 1) ->
- {ok, RE} = re:compile(RE0),
- Next = compile_expect(T),
- fun({timeout, _}=Subject) ->
- Next(Subject);
- (Subject) ->
- case re:run(Subject, RE, [{capture,first,index}]) of
- nomatch ->
- Next(Subject);
- {match, [{Pos,Len}]} ->
- Matched = binary:part(list_to_binary(Subject), Pos, Len),
- {matched, Pos+Len, Action(Matched)}
- end
- end;
-compile_expect([RE|T]) when is_list(RE) ->
- Ok = fun(_) -> ok end,
- compile_expect([{{re,list_to_binary(RE)},Ok}|T]);
-compile_expect([]) ->
- fun(_) ->
- nomatch
- end.
-
-rtnode_check_logs(Logname, Pattern, Logs) ->
-rtnode_check_logs(Logname, Pattern, true, Logs).
-rtnode_check_logs(Logname, Pattern, Match, Logs) ->
- case re:run(maps:get(Logname, Logs), Pattern) of
- {match, [_]} when Match ->
- ok;
- nomatch when not Match ->
- ok;
- _ ->
- rtnode_dump_logs(Logs),
- ct:fail("~p not found in log ~ts",[Pattern, Logname])
- end.
-
-rtnode_dump_logs(Logs) ->
- maps:foreach(
- fun(File, Data) ->
- ct:pal("~ts: ~ts",[File, Data])
- end, Logs).
-
-rtnode_read_logs(Tempdir) ->
- {ok, LogFiles0} = file:list_dir(Tempdir),
-
- %% Make sure that we only read log files and not any named pipes.
- LogFiles = [F || F <- LogFiles0,
- case F of
- "erlang.log" ++ _ -> true;
- _ -> false
- end],
-
- lists:foldl(
- fun(File, Acc) ->
- case file:read_file(filename:join(Tempdir, File)) of
- {ok, Data} ->
- Acc#{ File => Data };
- _ ->
- Acc
- end
- end, #{}, LogFiles).
-
-get_default_shell() ->
- try
- rtnode([{putline,""},
- {putline, "is_pid(whereis(user_drv))."},
- {expect, "true\r\n"}]),
- new
- catch _E:_R ->
- ?dbg({_E,_R}),
- old
- end.
-
%%
%% Test I/O-server
%%
--
2.35.3