File 0158-escript_SUITE-tempnam-use-priv_dir-and-command-name-.patch of Package erlang

From b86d4cf4a302a8aff19d519e4f89db3ab810c4ab Mon Sep 17 00:00:00 2001
From: Mikael Pettersson <mikpelinux@gmail.com>
Date: Sat, 26 Sep 2020 12:35:42 +0200
Subject: [PATCH 8/9] escript_SUITE: tempnam: use priv_dir and command name to
 create stderr file, remove retry logic

---
 lib/stdlib/test/escript_SUITE.erl | 156 ++++++++++++++----------------
 1 file changed, 72 insertions(+), 84 deletions(-)

diff --git a/lib/stdlib/test/escript_SUITE.erl b/lib/stdlib/test/escript_SUITE.erl
index 52c10711f4..d0098e98f8 100644
--- a/lib/stdlib/test/escript_SUITE.erl
+++ b/lib/stdlib/test/escript_SUITE.erl
@@ -37,7 +37,7 @@
 	 create_and_extract/1,
 	 foldl/1,
 	 overflow/1,
-	 verify_sections/3,
+	 verify_sections/4,
          unicode/1,
          bad_io_server/1
 	]).
@@ -82,31 +82,31 @@ end_per_testcase(_Case, _Config) ->
 basic(Config) when is_list(Config) ->
     Data = proplists:get_value(data_dir, Config),
     Dir = filename:absname(Data),		%Get rid of trailing slash.
-    run(Dir, "factorial 5",
+    run(Config, Dir, "factorial 5",
 	<<"factorial 5 = 120\nExitCode:0">>),
-    run(Dir, "factorial_compile 10",
+    run(Config, Dir, "factorial_compile 10",
 	<<"factorial 10 = 3628800\nExitCode:0">>),
-    run(Dir, "factorial_compile_main 7",
+    run(Config, Dir, "factorial_compile_main 7",
 	<<"factorial 7 = 5040\nExitCode:0">>),
-    run(Dir, "factorial_warning 20",
+    run(Config, Dir, "factorial_warning 20",
 	[data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\n"
 		    "factorial 20 = 2432902008176640000\nExitCode:0">>]),
-    run_with_opts(Dir, "-s", "factorial_warning",
+    run_with_opts(Config, Dir, "-s", "factorial_warning",
 		  [data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\nExitCode:0">>]),
-    run_with_opts(Dir, "-s -i", "factorial_warning",
+    run_with_opts(Config, Dir, "-s -i", "factorial_warning",
 		  [data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\nExitCode:0">>]),
-    run_with_opts(Dir, "-c -s", "factorial_warning",
+    run_with_opts(Config, Dir, "-c -s", "factorial_warning",
 		  [data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\nExitCode:0">>]),
-    run(Dir, "filesize "++filename:join(proplists:get_value(data_dir, Config),"filesize"),
+    run(Config, Dir, "filesize "++filename:join(proplists:get_value(data_dir, Config),"filesize"),
 	[data_dir,<<"filesize:11: Warning: function id/1 is unused\n324\nExitCode:0">>]),
-    run(Dir, "test_script_name",
+    run(Config, Dir, "test_script_name",
 	[data_dir,<<"test_script_name\nExitCode:0">>]),
-    run(Dir, "tail_rec 1000",
+    run(Config, Dir, "tail_rec 1000",
 	[<<"ok\nExitCode:0">>]),
 
     %% We expect the trap_exit flag for the process to be false,
     %% since that is the default state for newly spawned processes.
-    run(Dir, "trap_exit",
+    run(Config, Dir, "trap_exit",
 	<<"false\nExitCode:0">>),
     ok.
 
@@ -115,15 +115,15 @@ basic(Config) when is_list(Config) ->
 errors(Config) when is_list(Config) ->
     Data = proplists:get_value(data_dir, Config),
     Dir = filename:absname(Data),		%Get rid of trailing slash.
-    run(Dir, "compile_error",
+    run(Config, Dir, "compile_error",
 	[data_dir,<<"compile_error:5: syntax error before: '*'\n">>,
 	 data_dir,<<"compile_error:8: syntax error before: blarf\n">>,
 	 <<"escript: There were compilation errors.\nExitCode:127">>]),
-    run(Dir, "lint_error",
+    run(Config, Dir, "lint_error",
 	[data_dir,<<"lint_error:6: function main/1 already defined\n">>,
 	 data_dir,"lint_error:8: variable 'ExitCode' is unbound\n",
 	 <<"escript: There were compilation errors.\nExitCode:127">>]),
-    run_with_opts(Dir, "-s", "lint_error",
+    run_with_opts(Config, Dir, "-s", "lint_error",
 		  [data_dir,<<"lint_error:6: function main/1 already defined\n">>,
 		   data_dir,"lint_error:8: variable 'ExitCode' is unbound\n",
 		   <<"escript: There were compilation errors.\nExitCode:127">>]),
@@ -134,7 +134,7 @@ errors(Config) when is_list(Config) ->
 strange_name(Config) when is_list(Config) ->
     Data = proplists:get_value(data_dir, Config),
     Dir = filename:absname(Data),		%Get rid of trailing slash.
-    run(Dir, "strange.name -arg1 arg2 arg3",
+    run(Config, Dir, "strange.name -arg1 arg2 arg3",
 	[<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 	   "ExitCode:0">>]),
     ok.
@@ -144,7 +144,7 @@ strange_name(Config) when is_list(Config) ->
 emulator_flags(Config) when is_list(Config) ->
     Data = proplists:get_value(data_dir, Config),
     Dir = filename:absname(Data),		%Get rid of trailing slash.
-    run(Dir, "emulator_flags -arg1 arg2 arg3",
+    run(Config, Dir, "emulator_flags -arg1 arg2 arg3",
 	[<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 	   "nostick:[{nostick,[]}]\n"
 	   "mnesia:[{mnesia,[\"dir\",\"a/directory\"]},{mnesia,[\"debug\",\"verbose\"]}]\n"
@@ -158,7 +158,7 @@ emulator_flags(Config) when is_list(Config) ->
 two_lines(Config) when is_list(Config) ->
     Data = proplists:get_value(data_dir, Config),
     Dir = filename:absname(Data),		%Get rid of trailing slash.
-    run(Dir, "two_lines -arg1 arg2 arg3",
+    run(Config, Dir, "two_lines -arg1 arg2 arg3",
 	[<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 	   "ERL_FLAGS=false\n"
 	   "unknown:[]\n"
@@ -171,7 +171,7 @@ emulator_flags_no_shebang(Config) when is_list(Config) ->
     Data = proplists:get_value(data_dir, Config),
     Dir = filename:absname(Data),		%Get rid of trailing slash.
     %% Need run_with_opts, to always use "escript" explicitly
-    run_with_opts(Dir, "", "emulator_flags_no_shebang -arg1 arg2 arg3",
+    run_with_opts(Config, Dir, "", "emulator_flags_no_shebang -arg1 arg2 arg3",
 		  [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 		     "nostick:[{nostick,[]}]\n"
 		     "mnesia:[{mnesia,[\"dir\",\"a/directory\"]},{mnesia,[\"debug\",\"verbose\"]}]\n"
@@ -214,7 +214,7 @@ module_script(Config) when is_list(Config) ->
 			  ErlCode]),
     ok = file:write_file_info(NoArgsFile, OrigFI),
 
-    run(Dir, NoArgsBase ++ " -arg1 arg2 arg3",
+    run(Config, Dir, NoArgsBase ++ " -arg1 arg2 arg3",
 	[<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 	   "nostick:[]\n"
 	   "mnesia:[]\n"
@@ -222,7 +222,7 @@ module_script(Config) when is_list(Config) ->
 	   "unknown:[]\n"
 	   "ExitCode:0">>]),
 
-    run_with_opts(Dir, "", NoArgsBase ++  " -arg1 arg2 arg3",
+    run_with_opts(Config, Dir, "", NoArgsBase ++  " -arg1 arg2 arg3",
 		  [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 		     "nostick:[]\n"
 		     "mnesia:[]\n"
@@ -238,7 +238,7 @@ module_script(Config) when is_list(Config) ->
 			  ErlCode]),
     ok = file:write_file_info(NoArgsFile2, OrigFI),
 
-    run_with_opts(Dir, "", NoArgsBase2 ++  " -arg1 arg2 arg3",
+    run_with_opts(Config, Dir, "", NoArgsBase2 ++  " -arg1 arg2 arg3",
 		  [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 		     "nostick:[]\n"
 		     "mnesia:[]\n"
@@ -252,7 +252,7 @@ module_script(Config) when is_list(Config) ->
     ok = file:write_file(NoArgsFile3, [ErlCode]),
     ok = file:write_file_info(NoArgsFile3, OrigFI),
 
-    run_with_opts(Dir, "", NoArgsBase3 ++  " -arg1 arg2 arg3",
+    run_with_opts(Config, Dir, "", NoArgsBase3 ++  " -arg1 arg2 arg3",
 		  [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 		     "nostick:[]\n"
 		     "mnesia:[]\n"
@@ -273,7 +273,7 @@ module_script(Config) when is_list(Config) ->
 			  ErlCode]),
     ok = file:write_file_info(ArgsFile, OrigFI),
 
-    run(Dir, ArgsBase ++  " -arg1 arg2 arg3",
+    run(Config, Dir, ArgsBase ++  " -arg1 arg2 arg3",
 	[<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 	   "nostick:[{nostick,[]}]\n"
 	   "mnesia:[{mnesia,[\"dir\",\"a/directory\"]},{mnesia,[\"debug\",\"verbose\"]}]\n"
@@ -319,7 +319,7 @@ beam_script(Config) when is_list(Config) ->
 			  BeamCode]),
     ok = file:write_file_info(NoArgsFile, OrigFI),
 
-    run(Dir, NoArgsBase ++  " -arg1 arg2 arg3",
+    run(Config, Dir, NoArgsBase ++  " -arg1 arg2 arg3",
 	[<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 	   "nostick:[]\n"
 	   "mnesia:[]\n"
@@ -327,7 +327,7 @@ beam_script(Config) when is_list(Config) ->
 	   "unknown:[]\n"
 	   "ExitCode:0">>]),
 
-    run_with_opts(Dir, "", NoArgsBase ++  " -arg1 arg2 arg3",
+    run_with_opts(Config, Dir, "", NoArgsBase ++  " -arg1 arg2 arg3",
 		  [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 		     "nostick:[]\n"
 		     "mnesia:[]\n"
@@ -343,7 +343,7 @@ beam_script(Config) when is_list(Config) ->
 			  BeamCode]),
     ok = file:write_file_info(NoArgsFile2, OrigFI),
 
-    run_with_opts(Dir, "", NoArgsBase2 ++  " -arg1 arg2 arg3",
+    run_with_opts(Config, Dir, "", NoArgsBase2 ++  " -arg1 arg2 arg3",
 		  [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 		     "nostick:[]\n"
 		     "mnesia:[]\n"
@@ -357,7 +357,7 @@ beam_script(Config) when is_list(Config) ->
     ok = file:write_file(NoArgsFile3, [BeamCode]),
     ok = file:write_file_info(NoArgsFile3, OrigFI),
 
-    run_with_opts(Dir, "", NoArgsBase3 ++  " -arg1 arg2 arg3",
+    run_with_opts(Config, Dir, "", NoArgsBase3 ++  " -arg1 arg2 arg3",
 		  [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 		     "nostick:[]\n"
 		     "mnesia:[]\n"
@@ -378,7 +378,7 @@ beam_script(Config) when is_list(Config) ->
 			  BeamCode]),
     ok = file:write_file_info(ArgsFile, OrigFI),
 
-    run(Dir, ArgsBase ++  " -arg1 arg2 arg3",
+    run(Config, Dir, ArgsBase ++  " -arg1 arg2 arg3",
 	[<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 	   "nostick:[{nostick,[]}]\n"
 	   "mnesia:[{mnesia,[\"dir\",\"a/directory\"]},{mnesia,[\"debug\",\"verbose\"]}]\n"
@@ -435,14 +435,14 @@ archive_script(Config) when is_list(Config) ->
 			  ArchiveBin]),
     ok = file:write_file_info(MainScript, OrigFI),
 
-    run(PrivDir, MainBase ++  " -arg1 arg2 arg3",
+    run(Config, PrivDir, MainBase ++  " -arg1 arg2 arg3",
 	[<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 	   "dict:[{archive_script_dict,[\"foo\",\"bar\"]},{archive_script_dict,[\"foo\"]}]\n"
 	   "dummy:[{archive_script_dummy,[\"bar\"]}]\n"
 	   "priv:{ok,<<\"Some private data...\\n\">>}\n"
 	   "ExitCode:0">>]),
 
-    run_with_opts(PrivDir, "", MainBase ++  " -arg1 arg2 arg3",
+    run_with_opts(Config, PrivDir, "", MainBase ++  " -arg1 arg2 arg3",
 		  [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 		     "dict:[{archive_script_dict,[\"foo\",\"bar\"]},{archive_script_dict,[\"foo\"]}]\n"
 		     "dummy:[{archive_script_dummy,[\"bar\"]}]\n"
@@ -457,7 +457,7 @@ archive_script(Config) when is_list(Config) ->
 			  ArchiveBin]),
     ok = file:write_file_info(MainScript, OrigFI),
 
-    run_with_opts(PrivDir, "", MainBase ++  " -arg1 arg2 arg3",
+    run_with_opts(Config, PrivDir, "", MainBase ++  " -arg1 arg2 arg3",
 		  [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 		     "dict:[]\n"
 		     "dummy:[]\n"
@@ -470,7 +470,7 @@ archive_script(Config) when is_list(Config) ->
     ok = file:write_file(MainScript, [ArchiveBin]),
     ok = file:write_file_info(MainScript, OrigFI),
 
-    run_with_opts(PrivDir, "", MainBase ++  " -arg1 arg2 arg3",
+    run_with_opts(Config, PrivDir, "", MainBase ++  " -arg1 arg2 arg3",
 		  [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 		     "dict:[]\n"
 		     "dummy:[]\n"
@@ -489,7 +489,7 @@ archive_script(Config) when is_list(Config) ->
 			  ArchiveBin]),
     ok = file:write_file_info(AltScript, OrigFI),
 
-    run(PrivDir, AltBase ++  " -arg1 arg2 arg3",
+    run(Config, PrivDir, AltBase ++  " -arg1 arg2 arg3",
 	[<<"main2:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 	   "dict:[{archive_script_dict,[\"foo\",\"bar\"]},{archive_script_dict,[\"foo\"]}]\n"
 	   "dummy:[{archive_script_dummy,[\"bar\"]}]\n"
@@ -589,7 +589,7 @@ archive_script_file_access(Config) when is_list(Config) ->
 
     %% Change to script's directory and run it as "./<script_name>"
     ok = file:set_cwd(PrivDir),
-    run(PrivDir, "./" ++ ScriptName1 ++ " " ++ ScriptName1,
+    run(Config, PrivDir, "./" ++ ScriptName1 ++ " " ++ ScriptName1,
 	[<<"ExitCode:0">>]),
     ok = file:set_cwd(TopDir),
 
@@ -623,7 +623,7 @@ archive_script_file_access(Config) when is_list(Config) ->
 
     %% Change to script's directory and run it as "./<script_name>"
     ok = file:set_cwd(PrivDir),
-    run(PrivDir, "./" ++ ScriptName2 ++ " " ++ ScriptName2,
+    run(Config, PrivDir, "./" ++ ScriptName2 ++ " " ++ ScriptName2,
 	[<<"ExitCode:0">>]),
 
     %% 3. If symlinks are supported, run one of the scripts via a symlink.
@@ -631,7 +631,7 @@ archive_script_file_access(Config) when is_list(Config) ->
     %% This is in order to test error b) described above this test case.
     case element(1,os:type()) =:= win32 orelse file:read_link(Symlink2) of
 	{ok,_} ->
-	    run(PrivDir, "./" ++ SymlinkName2 ++ " " ++ ScriptName2,
+	    run(Config, PrivDir, "./" ++ SymlinkName2 ++ " " ++ ScriptName2,
 		[<<"ExitCode:0">>]);
 	_ -> % not supported
 	    ok
@@ -667,7 +667,7 @@ compile_files([], _, _) ->
 epp(Config) when is_list(Config) ->
     Data = proplists:get_value(data_dir, Config),
     Dir = filename:absname(Data),		%Get rid of trailing slash.
-    run(Dir, "factorial_epp 5",
+    run(Config, Dir, "factorial_epp 5",
 	<<"factorial 5 = 120\nExitCode:0">>),
     ok.
 
@@ -687,7 +687,7 @@ create_and_extract(Config) when is_list(Config) ->
 	 [{archive, ArchiveBin}]],
 
     %% Verify all combinations of scripts with shebangs
-    [verify_sections(NewFile, FileInfo, S ++ C ++ E ++ B) ||
+    [verify_sections(Config, NewFile, FileInfo, S ++ C ++ E ++ B) ||
 	S <- [[{shebang, default}],
 	      [{shebang, "/usr/bin/env     escript"}]],
 	C <- [[],
@@ -700,7 +700,7 @@ create_and_extract(Config) when is_list(Config) ->
 	B <- [[{source, Source}] | Bodies]],
 
     %% Verify all combinations of scripts without shebangs
-    [verify_sections(NewFile, FileInfo, S ++ C ++ E ++ B) ||
+    [verify_sections(Config, NewFile, FileInfo, S ++ C ++ E ++ B) ||
 	S <- [[], [{shebang, undefined}]],
 	C <- [[], [{comment, undefined}]],
 	E <- [[], [{emu_args, undefined}]],
@@ -712,7 +712,7 @@ create_and_extract(Config) when is_list(Config) ->
     {ok, [_, _, _, {source, Source}]} = escript:extract(NewFile, []),
     {ok, [_, _, _, {source, BeamCode2}]} =
 	escript:extract(NewFile, [compile_source]),
-    verify_sections(NewFile, FileInfo,
+    verify_sections(Config, NewFile, FileInfo,
 		    [{shebang, default},
 		     {comment, default},
 		     {beam, BeamCode2}]),
@@ -756,7 +756,7 @@ prepare_creation(Base, Config) ->
      Base ++ ".beam", BeamCode,
      ArchiveBin}.
 
-verify_sections(File, FileInfo, Sections) ->
+verify_sections(Config, File, FileInfo, Sections) ->
     io:format("~p:verify_sections(\n\t~p,\n\t~p,\n\t~p).\n",
 	      [?MODULE, File, FileInfo, Sections]),
 
@@ -793,9 +793,9 @@ verify_sections(File, FileInfo, Sections) ->
     Expected = <<ExpectedMain/binary, ExpectedOutput/binary>>,
     case HasArg(shebang) of
 	true ->
-	    run(Dir, InputArgs, [Expected]);
+	    run(Config, Dir, InputArgs, [Expected]);
 	false ->
-	    run_with_opts(Dir, [], InputArgs, [Expected])
+	    run_with_opts(Config, Dir, [], InputArgs, [Expected])
     end,
 
     %% Verify
@@ -924,18 +924,18 @@ emulate_escript_foldl(Fun, Acc, File) ->
 unicode(Config) when is_list(Config) ->
     Data = proplists:get_value(data_dir, Config),
     Dir = filename:absname(Data),		%Get rid of trailing slash.
-    run(Dir, "unicode1",
+    run(Config, Dir, "unicode1",
         [<<"escript: exception error: an error occurred when evaluating"
            " an arithmetic expression\n  in operator  '/'/2\n     "
            "called as <<224,170,170>> / <<224,170,170>>\nExitCode:127">>]),
-    run(Dir, "unicode2",
+    run(Config, Dir, "unicode2",
         [<<"escript: exception error: an error occurred when evaluating"
            " an arithmetic expression\n  in operator  '/'/2\n     "
            "called as <<\"\xaa\">> / <<\"\xaa\">>\nExitCode:127">>]),
-    run(Dir, "unicode3", [<<"ExitCode:0">>]),
-    run(Dir, "unicode4", [<<"ExitCode:0">>]),
-    run(Dir, "unicode5", [<<"ExitCode:0">>]),
-    run(Dir, "unicode6", [<<"ExitCode:0">>]),
+    run(Config, Dir, "unicode3", [<<"ExitCode:0">>]),
+    run(Config, Dir, "unicode4", [<<"ExitCode:0">>]),
+    run(Config, Dir, "unicode5", [<<"ExitCode:0">>]),
+    run(Config, Dir, "unicode6", [<<"ExitCode:0">>]),
     ok.
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -943,9 +943,9 @@ unicode(Config) when is_list(Config) ->
 overflow(Config) when is_list(Config) ->
     Data = proplists:get_value(data_dir, Config),
     Dir = filename:absname(Data),		%Get rid of trailing slash.
-    run(Dir, "arg_overflow",
+    run(Config, Dir, "arg_overflow",
 	[<<"ExitCode:0">>]),
-    run(Dir, "linebuf_overflow",
+    run(Config, Dir, "linebuf_overflow",
 	[<<"ExitCode:0">>]),
     ok.
 
@@ -955,37 +955,31 @@ overflow(Config) when is_list(Config) ->
 bad_io_server(Config) when is_list(Config) ->
     Data = proplists:get_value(data_dir, Config),
     Dir = filename:absname(Data),		%Get rid of trailing slash.
-    run(Dir, "bad_io_server",
+    run(Config, Dir, "bad_io_server",
         [<<"escript: exception error: an error occurred when evaluating"
            " an arithmetic expression\n  in operator  '/'/2\n     "
            "called as '\\x{400}' / 0\nExitCode:127">>]),
     ok.
 
-run(Dir, Cmd0, Expected0) ->
+run(Config, Dir, Cmd0, Expected0) ->
+    [CmdName | _] = string:split(Cmd0, " ", all),
     Expected = iolist_to_binary(expected_output(Expected0, Dir)),
     Cmd = case os:type() of
 	      {win32,_} -> "escript " ++ filename:nativename(Dir) ++ "\\" ++ Cmd0;
 	      _ -> Cmd0
 	  end,
-    do_run(Dir, Cmd, Expected).
+    do_run(Config, CmdName, Dir, Cmd, Expected).
 
-run_with_opts(Dir, Opts, Cmd0, Expected) ->
+run_with_opts(Config, Dir, Opts, Cmd0, Expected) ->
+    [CmdName | _] = string:split(Cmd0, " ", all),
     Cmd = case os:type() of
 	      {win32,_} -> "escript " ++ Opts ++ " " ++ filename:nativename(Dir) ++ "\\" ++ Cmd0;
 	      _ -> "escript " ++ Opts ++ " " ++ Dir ++ "/" ++ Cmd0
 	  end,
-    do_run(Dir, Cmd, Expected).
+    do_run(Config, CmdName, Dir, Cmd, Expected).
 
-do_run(Dir, Cmd, Expected) ->
-    case tempnam("escript_stderr") of
-	{ok, StdErrFile} ->
-	    do_run(Dir, Cmd, Expected, StdErrFile);
-	{error, Reason} ->
-	    io:format("Failed to create temp file: ~p\n", [Reason]),
-	    ct:fail(failed)
-    end.
-
-do_run(Dir, Cmd0, Expected0, StdErrFile) ->
+do_run(Config, CmdName, Dir, Cmd0, Expected0) ->
+    StdErrFile = tempnam(Config, CmdName),
     Cmd = Cmd0 ++ " 2> " ++ StdErrFile,
     io:format("Run: ~p\n", [Cmd]),
     Expected = iolist_to_binary(expected_output(Expected0, Dir)),
@@ -1030,27 +1024,21 @@ delete_first(_X, [], _Acc) -> false;
 delete_first(X, [X | Tail], Acc) -> lists:reverse(Acc, Tail);
 delete_first(X, [Y | Tail], Acc) -> delete_first(X, Tail, [Y | Acc]).
 
-tempnam(Prefix) ->
-    Dir = os:getenv("TMPDIR", "/tmp"),
-    Pid = os:getpid(),
-    %% Using rand's functional API requires knowing the set of available
-    %% algorithms, and which one is default.  Unfortunately both properties
-    %% tend to change between OTP releases.
-    Algorithm = exsss,
-    RandState = rand:seed_s(Algorithm, os:timestamp()),
-    tempnam(filename:join(Dir, Prefix ++ "_" ++ Pid ++ "_"), RandState, _Retries = 10).
-
-tempnam(_Prefix, _RandState, _Retries = 0) -> {error, ebusy};
-tempnam(Prefix, RandState0, Retries) ->
-    {RandNr, RandState} = rand:uniform_s(1 bsl 32, RandState0),
-    File = Prefix ++ integer_to_list(RandNr),
+tempnam(Config, Prefix) ->
+    Dir = proplists:get_value(priv_dir, Config),
+    File = filename:join(Dir, Prefix ++ ".stderr"),
+    case file:delete(File) of
+	ok -> ok;
+	{error, enoent} -> ok
+    end,
     case file:open(File, [write, exclusive, raw]) of
 	{ok, IoDev} ->
 	    ok = file:close(IoDev),
 	    ok = file:delete(File),
-	    {ok, File};
-	{error, _Reason} ->
-	    tempnam(Prefix, RandState, Retries - 1)
+	    File;
+	{error, Reason} ->
+	    io:format("Failed to create ~s: ~p\n", [File, Reason]),
+	    ct:fail(failed)
     end.
 
 get_data(Port, SoFar) ->
-- 
2.26.2

openSUSE Build Service is sponsored by