File 3162-erts-Fix-S-and-extra-to-work-as-they-should.patch of Package erlang

From 1b866743244edaf4e662e0047dde5cce1738339e Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Fri, 8 Sep 2023 13:42:32 +0200
Subject: [PATCH] erts: Fix -S and -extra to work as they should

-S is now only allowed on the command line and is
handled as any other flag when passed as an environment
flag.

-extra now correctly strips "--" when added by erlexec

Improved error reporting for -S, -s and -run.

Updated docs to correctly describe how -S and -extra work.
---
 erts/doc/src/init.xml          |  26 +++-
 erts/etc/common/erlexec.c      | 103 +++++++++------
 erts/preloaded/ebin/init.beam  | Bin 62436 -> 63948 bytes
 erts/preloaded/src/init.erl    |  70 ++++++++---
 lib/kernel/test/init_SUITE.erl | 223 ++++++++++++++++++++++++++++++++-
 5 files changed, 362 insertions(+), 60 deletions(-)

diff --git a/erts/doc/src/init.xml b/erts/doc/src/init.xml
index 0c358ba8c7..94d4241403 100644
--- a/erts/doc/src/init.xml
+++ b/erts/doc/src/init.xml
@@ -309,6 +309,27 @@ BF</pre>
           arguments and can be retrieved using
           <seemfa marker="#get_plain_arguments/0">
           <c>get_plain_arguments/0</c></seemfa>.</p>
+        <p>Example:</p>
+        <pre>
+% <input>erl -extra +A 1 --</input>
+...
+1> <input>init:get_plain_arguments().</input>
+["+A","1","--"]
+        </pre>
+        <p>The <c>-extra</c> flag can be passed on the command line,
+          through <c>ERL_*FLAGS</c> or <c>-args_file</c>. It only effects
+          the remaining command-line flags in the entity in which it is passed.
+          If multiple <c>-extra</c> flags are passed they are concatenated using
+          the same order rules as <c>ERL_*FLAGS</c> or <c>-args_file</c> in which
+          they are given.
+        </p>
+        <p>Example:</p>
+        <pre>
+% <input>ERL_AFLAGS="-extra a" ERL_ZFLAGS="-extra d" erl -extra b -extra c</input>
+...
+1> <input>init:get_plain_arguments().</input>
+["a","b","-extra","c","d"]
+        </pre>
       </item>
       <tag><c>-S Mod [Func [Arg1, Arg2, ...]]</c></tag>
       <item>
@@ -321,7 +342,7 @@ BF</pre>
           error message.</p>
         <p>Example:</p>
         <pre>
-          % <input>erl -S httpd serve --port 8080 /var/www/html</input></pre>
+% <input>erl -S httpd serve --port 8080 /var/www/html</input></pre>
         <p>This starts the Erlang runtime system and evaluates
           the function <c>httpd:serve(["--port", "8080", "/var/www/html"])</c>.
           All arguments up to the end of the command line will be passed
@@ -331,6 +352,9 @@ BF</pre>
           the user. This means that a <c>-S</c> call that does not
           return blocks further processing; to avoid this, use
           some variant of <c>spawn</c> in such cases.</p>
+        <p>The <c>-S</c> flag is only allowed on the command line. If passed
+          through <c>ERL_*FLAGS</c> or <c>-args_file</c> it will be parsed
+          as a normal command line flag.</p>
       </item>
       <tag><c>-run Mod [Func [Arg1, Arg2, ...]]</c></tag>
       <item>
diff --git a/erts/etc/common/erlexec.c b/erts/etc/common/erlexec.c
index 888df87e35..5f16586696 100644
--- a/erts/etc/common/erlexec.c
+++ b/erts/etc/common/erlexec.c
@@ -183,6 +183,7 @@ static char *plusz_val_switches[] = {
 #endif
 
 #define DEFAULT_SUFFIX	  "smp"
+char *sep = "--";
 
 void usage(const char *switchname);
 static void usage_format(char *format, ...);
@@ -405,7 +406,7 @@ static void add_boot_config(void)
 
 #define NEXT_ARG_CHECK_NAMED(Option) \
     do {                                                                \
-        if (i+1 >= argc || strncmp(argv[i+1], "--", 3) == 0)            \
+        if (i+1 >= argc || strncmp(argv[i+1], sep, 3) == 0)            \
             usage(Option);                                              \
     } while(0)
 
@@ -516,6 +517,9 @@ int main(int argc, char **argv)
 		goto smp_disable;
 	    } else if (strcmp(argv[i], "-extra") == 0) {
 		break;
+            } else if (strcmp(argv[i], "++S") == 0) {
+                /* This is a -S passed on command line */
+		break;
 	    } else if (strcmp(argv[i], "-emu_type") == 0) {
                 NEXT_ARG_CHECK();
                 emu_type = argv[i+1];
@@ -593,7 +597,7 @@ int main(int argc, char **argv)
 
     add_epmd_port();
 
-    add_arg("--");
+    add_arg(sep);
 
     while (i < argc) {
 	if (!process_args) {	/* Copy arguments after '-extra' */
@@ -806,9 +810,7 @@ int main(int argc, char **argv)
 		    }
 		    else
 			add_arg(argv[i]);
-		
 		    break;
-	
 		  case 'v':	/* -version */
 		    if (strcmp(argv[i], "-version") == 0) {
 			add_Eargs("-V");
@@ -1028,6 +1030,17 @@ int main(int argc, char **argv)
 			  i++;
 		      }
 		      break;
+                  case '+':
+                    if (strcmp(argv[i], "++S") == 0) {
+                        /* This is a -S passed on command line */
+			process_args = 0;
+			ADD_BOOT_CONFIG;
+			add_arg("-S");
+                    } else {
+			add_arg(argv[i]);
+                    }
+                    break;
+
 		  default:
 		  the_default:
 		    argv[i][0] = '-'; /* Change +option to -option. */
@@ -1043,6 +1056,7 @@ int main(int argc, char **argv)
     }
 
     efree(emu_name);
+    efree(argv);
 
     if (process_args) {
 	ADD_BOOT_CONFIG;
@@ -1082,14 +1096,14 @@ int main(int argc, char **argv)
     }
 #endif
 
-    add_Eargs("--");
+    add_Eargs(sep);
     add_Eargs("-root");
     add_Eargs(rootdir);
     add_Eargs("-bindir");
     add_Eargs(bindir);
     add_Eargs("-progname");
     add_Eargs(progname);
-    add_Eargs("--");
+    add_Eargs(sep);
     ensure_EargsSz(EargsCnt + argsCnt + 1);
     for (i = 0; i < argsCnt; i++)
 	Eargsp[EargsCnt++] = argsp[i];
@@ -1711,6 +1725,7 @@ static char **build_args_from_string(char *string, int allow_comments)
     int s_alloced = 0;
     int s_pos = 0;
     char *p = string;
+    int has_extra = !!0;
     enum {Start, Build, Build0, BuildSQuoted, BuildDQuoted, AcceptNext, BuildComment} state;
 
 #define ENSURE()					\
@@ -1781,6 +1796,9 @@ static char **build_args_from_string(char *string, int allow_comments)
 	    case '\0':
 		ENSURE();
 		(*cur_s)[s_pos] = '\0';
+                if (strcmp(*cur_s, "-extra") == 0) {
+                    has_extra = !0;
+                }
 		++argc;
 		state = Start;
 		break;
@@ -1852,9 +1870,10 @@ done:
 	efree(argv);
 	return NULL;
     }
-    argv[argc++] = "--"; /* Add a -- separator in order
-                            for flags from different environments
-                            to not effect each other */
+    if (!has_extra)
+        argv[argc++] = sep; /* Add a -- separator in order
+                               for flags from different environments
+                               to not effect each other */
     argv[argc++] = NULL; /* Sure to be large enough */
     return argv;
 #undef ENSURE
@@ -2075,18 +2094,22 @@ get_file_args(char *filename, argv_buf *abp, argv_buf *xabp)
 }
 
 static void
-initial_argv_massage(int *argc, char ***argv)
+initial_argv_massage(int *argc, char ***argvp)
 {
-    argv_buf ab = {0}, xab = {0};
+    argv_buf ab = {0}, xab = {0}, sab = {0};
     int ix, vix, ac;
     char **av;
-    char *sep = "--";
+    char **argv = &(*argvp)[0];
     struct {
 	int argc;
 	char **argv;
     } avv[] = {{INT_MAX, NULL}, {INT_MAX, NULL}, {INT_MAX, NULL},
 	       {INT_MAX, NULL}, {INT_MAX, NULL},
                {INT_MAX, NULL}, {INT_MAX, NULL}};
+
+    /* Save program name */
+    save_arg(&ab, argv[0]);
+
     /*
      * The environment flag containing OTP release is intentionally
      * undocumented and intended for OTP internal use only.
@@ -2105,7 +2128,7 @@ initial_argv_massage(int *argc, char ***argv)
     /* command line */
     if (*argc > 1) {
 	avv[vix].argc = *argc - 1;
-	avv[vix++].argv = &(*argv)[1];
+	avv[vix++].argv = argv + 1;
         avv[vix].argc = 1;
         avv[vix++].argv = &sep;
     }
@@ -2117,30 +2140,7 @@ initial_argv_massage(int *argc, char ***argv)
     av = build_args_from_env("ERL_ZFLAGS");
     if (av)
 	avv[vix++].argv = av;
-
-    if (vix == (*argc > 1 ? 2 : 0)) {
-	/* Only command line argv; check if we can use argv as it is... */
-	ac = *argc;
-	av = *argv;
-	for (ix = 1; ix < ac; ix++) {
-	    if (strcmp(av[ix], "-args_file") == 0) {
-		/* ... no; we need to expand arguments from
-		   file into argument list */
-		goto build_new_argv;
-	    }
-	    if (strcmp(av[ix], "-extra") == 0) {
-		break;
-	    }
-	}
-
-	/* ... yes; we can use argv as it is. */
-	return;
-    }
-
- build_new_argv:
-
-    save_arg(&ab, (*argv)[0]);
-
+    
     vix = 0;
     while (avv[vix].argv) {
 	ac = avv[vix].argc;
@@ -2158,8 +2158,27 @@ initial_argv_massage(int *argc, char ***argv)
 		    ix++;
 		    while (ix < ac && av[ix])
 			save_arg(&xab, av[ix++]);
+                    save_arg(&ab, sep);
 		    break;
-		}
+		} else if (ac != INT_MAX && strcmp(av[ix], "-S") == 0) {
+                    /* If we are looking at command line and find -S */
+                    ix++;
+                    /* We use ++S instead of -S here in order to differentiate
+                       this -S from any passed as environment flags. */
+                    save_arg(&sab, "++S");
+                    while (ix < ac && av[ix]) {
+                        if (strcmp(av[ix], sep) == 0) {
+                            ix++;
+                            /* Escape any -- with \-- so that we know that
+                               this is a literal -- and not one added by erlexec */
+                            save_arg(&sab, "\\--");
+                        } else {
+                            save_arg(&sab, av[ix++]);
+                        }
+                    }
+                    save_arg(&ab, sep);
+		    break;
+                }
 		save_arg(&ab, av[ix++]);
 	    }
 	}
@@ -2181,9 +2200,15 @@ initial_argv_massage(int *argc, char ***argv)
 	efree(xab.argv);
     }
 
+    if (sab.argc) {
+	for (ix = 0; ix < sab.argc; ix++)
+	    save_arg(&ab, sab.argv[ix]);
+	efree(sab.argv);
+    }
+
     save_arg(&ab, NULL);
     trim_argv_buf(&ab);
-    *argv = ab.argv;
+    *argvp = ab.argv;
     *argc = ab.argc - 1;
 }
 
diff --git a/erts/preloaded/src/init.erl b/erts/preloaded/src/init.erl
index 1b9af02591..f4f3bfdb98 100644
--- a/erts/preloaded/src/init.erl
+++ b/erts/preloaded/src/init.erl
@@ -49,6 +49,8 @@
 
 -module(init).
 
+-feature(maybe_expr, enable).
+
 -export([restart/1,restart/0,reboot/0,stop/0,stop/1,
 	 get_status/0,boot/1,get_arguments/0,get_plain_arguments/0,
 	 get_argument/1,script_id/0,script_name/0]).
@@ -279,7 +281,7 @@ run_args_to_mfa([]) ->
       "Error! The -S option must be followed by at least a module to start, such as "
       "`-S Module` or `-S Module Function` to start with a function.\r\n\r\n"
     ),
-    erlang:error(undef);
+    halt();
 run_args_to_mfa([M]) -> {b2a(M), start, []};
 run_args_to_mfa([M, F]) -> {b2a(M), b2a(F), []};
 run_args_to_mfa([M, F | A]) -> {b2a(M), b2a(F), [A]}.
@@ -1220,7 +1222,21 @@ start_it({eval,Bin}) ->
 start_it({apply,M,F,Args}) ->
     case code:ensure_loaded(M) of
         {module, M} ->
-            apply(M, F, Args);
+            try apply(M, F, Args)
+            catch error:undef:ST ->
+                    maybe
+                        false ?= erlang:function_exported(M, F, length(Args)),
+                        Message = ["Error! ",atom_to_binary(M),":",
+                                   atom_to_list(F),"/",integer_to_list(length(Args)),
+                                   " is not exported."
+                                   "\r\n\r\n"],
+                        erlang:display_string(binary_to_list(iolist_to_binary(Message)))
+                    end,
+                    erlang:raise(error,undef,ST);
+                  E:R:ST ->
+                    erlang:display({E,R,ST}),
+                    erlang:raise(E,R,ST)
+            end;
         {error, Reason} ->
             Message = [explain_ensure_loaded_error(M, Reason), <<"\r\n\r\n">>],
             erlang:display_string(binary_to_list(iolist_to_binary(Message))),
@@ -1234,8 +1250,9 @@ explain_ensure_loaded_error(M, badfile) ->
          erlang:system_info(otp_release), <<".)">>],
     explain_add_head(M, S);
 explain_ensure_loaded_error(M, nofile) ->
-    S = <<"it cannot be found. Make sure that the module name is correct and\r\n",
-          "that its .beam file is in the code path.">>,
+    S = <<"it cannot be found.\r\n",
+          "Make sure that the module name is correct and that its .beam file\r\n",
+          "is in the code path.">>,
     explain_add_head(M, S);
 explain_ensure_loaded_error(M, Other) ->
     [<<"Error! Failed to load module '", (atom_to_binary(M))/binary,
@@ -1306,7 +1323,7 @@ parse_boot_args(Args) ->
     parse_boot_args(Args, [], [], []).
 
 parse_boot_args([B|Bs], Ss, Fs, As) ->
-    case check(B) of
+    case check(B, Bs) of
 	start_extra_arg ->
 	    {reverse(Ss),reverse(Fs),lists:reverse(As, Bs)}; % BIF
 	start_arg ->
@@ -1322,9 +1339,14 @@ parse_boot_args([B|Bs], Ss, Fs, As) ->
             %% Forward any additional arguments to the function we are calling,
             %% such that no init:get_plain_arguments is needed by it later.
             MFA = run_args_to_mfa(S ++ Rest),
-            {M, F, A} = interpolate_empty_mfa_args(MFA),
-            StartersWithThis = [{apply, M, F, map(fun bs2ss/1, A)} | Ss],
-            {reverse(StartersWithThis),reverse(Fs),[]};
+            {M, F, [Args]} = interpolate_empty_mfa_args(MFA),
+            StartersWithThis = [{apply, M, F,
+                                 %% erlexec escapes and -- passed after -S
+                                 %% so we un-escape it
+                                 [map(fun("\\--") -> "--";
+                                         (A) -> A
+                                      end, map(fun b2s/1, Args))]} | Ss],
+            {reverse(StartersWithThis),reverse(Fs),reverse(As)};
 	eval_arg ->
 	    {Expr,Rest} = get_args(Bs, []),
             parse_boot_args(Rest, [{eval, fold_eval_args(Expr)} | Ss], Fs, As);
@@ -1340,17 +1362,31 @@ parse_boot_args([B|Bs], Ss, Fs, As) ->
 parse_boot_args([], Start, Flags, Args) ->
     {reverse(Start),reverse(Flags),reverse(Args)}.
 
-check(<<"-extra">>) -> start_extra_arg;
-check(<<"-s">>) -> start_arg;
-check(<<"-run">>) -> start_arg2;
-check(<<"-S">>) -> ending_start_arg;
-check(<<"-eval">>) -> eval_arg;
-check(<<"--">>) -> end_args;
-check(<<"-",Flag/binary>>) -> {flag,b2a(Flag)};
-check(_) -> arg.
+check(<<"-extra">>, _Bs) ->
+    start_extra_arg;
+check(<<"-s">>, _Bs) -> start_arg;
+check(<<"-run">>, _Bs) -> start_arg2;
+check(<<"-S">>, Bs) ->
+    case has_end_args(Bs) of
+        true ->
+            {flag, b2a(<<"S">>)};
+        false ->
+            ending_start_arg
+    end;
+check(<<"-eval">>, _Bs) -> eval_arg;
+check(<<"--">>, _Bs) -> end_args;
+check(<<"-",Flag/binary>>, _Bs) -> {flag,b2a(Flag)};
+check(_,_) -> arg.
+
+has_end_args([<<"--">> | _Bs]) ->
+    true;
+has_end_args([_ | Bs]) ->
+    has_end_args(Bs);
+has_end_args([]) ->
+    false.
 
 get_args([B|Bs], As) ->
-    case check(B) of
+    case check(B, Bs) of
 	start_extra_arg -> {reverse(As), [B|Bs]};
 	start_arg -> {reverse(As), [B|Bs]};
 	start_arg2 -> {reverse(As), [B|Bs]};
diff --git a/lib/kernel/test/init_SUITE.erl b/lib/kernel/test/init_SUITE.erl
index ea75f040f2..46fd0199d2 100644
--- a/lib/kernel/test/init_SUITE.erl
+++ b/lib/kernel/test/init_SUITE.erl
@@ -21,6 +21,7 @@
 
 -include_lib("common_test/include/ct.hrl").
 -include_lib("stdlib/include/assert.hrl").
+-feature(maybe_expr, enable).
 
 -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 	 init_per_group/2,end_per_group/2]).
@@ -29,9 +30,13 @@
 	 many_restarts/0, many_restarts/1, restart_with_mode/1,
 	 get_plain_arguments/1,
 	 reboot/1, stop_status/1, stop/1, get_status/1, script_id/1,
-         dot_erlang/1, unknown_module/1,
-	 find_system_processes/0]).
+         dot_erlang/1, unknown_module/1, dash_S/1, dash_extra/1,
+         dash_run/1, dash_s/1,
+	 find_system_processes/0
+         ]).
 -export([boot1/1, boot2/1]).
+-export([test_dash_S/1, test_dash_s/1, test_dash_extra/0,
+         test_dash_run/0, test_dash_run/1]).
 
 -export([init_per_testcase/2, end_per_testcase/2]).
 
@@ -48,7 +53,8 @@ all() ->
     [get_arguments, get_argument, boot_var,
      many_restarts, restart_with_mode,
      get_plain_arguments, restart, stop_status, get_status, script_id,
-     dot_erlang, unknown_module, {group, boot}].
+     dot_erlang, unknown_module, {group, boot},
+     dash_S, dash_extra, dash_run, dash_s].
 
 groups() -> 
     [{boot, [], [boot1, boot2]}].
@@ -748,6 +754,217 @@ boot2(Config) when is_list(Config) ->
 
     ok.
 
+dash_S(_Config) ->
+
+    %% Test that arguments are passed correctly
+    {[],[],[]} = run_dash_S_test([]),
+    {["a"],[],[]} = run_dash_S_test(["a"]),
+    {["-S","--"],[],[]} = run_dash_S_test(["-S","--"]),
+    {["--help"],[],[]} = run_dash_S_test(["--help"]),
+    {["-extra"],[],[]} = run_dash_S_test(["-extra"]),
+    {["-run"],[],[]} = run_dash_S_test(["-run"]),
+    {["-args_file"],[],[]} = run_dash_S_test(["-args_file"]),
+    {["+A","-1"],[],[]} = run_dash_S_test(["+A","-1"]),
+    {["-s","init","stop"],[],[]} = run_dash_S_test(["-s","init","stop"]),
+
+    %% Test that environment variables are handled correctly
+    {["a"],["b","c","d"],[]} =
+        run_dash_S_test([{"ERL_AFLAGS","b"},{"ERL_FLAGS","c"},{"ERL_ZFLAGS","d"}],["a"]),
+    %% test that -S in environment variables are interpreted as flags
+    {["a"],[],[["a"],["b"],["c"]]} =
+        run_dash_S_test([{"ERL_AFLAGS","+S 1 -S a"},{"ERL_FLAGS","-S b"},
+                         {"ERL_ZFLAGS","-S c"}],["a"]),
+
+    %% Test that -s and -run work
+    ?assertMatch(
+       "[a].{[\"a\""++_,
+       run_dash_test(["-s",?MODULE,"test_dash_s","a","-S",?MODULE,"test_dash_S","a"])),
+    ?assertMatch(
+       "[\"a\"].{[\"a\""++_,
+       run_dash_test(["-run",?MODULE,"test_dash_s","a","-S",?MODULE,"test_dash_S","a"])),
+
+    %% Test error conditions
+    ?assertNotEqual(
+       nomatch,
+       string:find(run_dash_test(["-S"]),
+                   "Error! The -S option must be followed by at least a module to start")),
+
+    ?assertNotEqual(
+       nomatch,
+       string:find(run_dash_test(["-S","a"]),
+                   "Error! Failed to load module 'a' because it cannot be found.")),
+
+    ?assertNotEqual(
+       nomatch,
+       string:find(run_dash_test(["-S",?MODULE,"a"]),
+                   "Error! init_SUITE:a/1 is not exported.")),
+
+    ok.
+
+run_dash_S_test(Args) ->
+    run_dash_S_test("", Args).
+run_dash_S_test(Prefix, Args) ->
+    run_dash_test(Prefix, ["-S", ?MODULE, "test_dash_S" | Args]).
+
+test_dash_S(Args) ->
+    AllArgs = {Args, init:get_plain_arguments(),
+               proplists:get_all_values('S',init:get_arguments()),
+               erlang:system_info(emu_args)},
+    io:format("~p.",[AllArgs]),
+    erlang:halt().
+
+test_dash_s(Args) ->
+    io:format("~p.",[Args]).
+
+dash_run(_Config) ->
+
+    {undefined,[]} =
+        run_dash_test(["-run",?MODULE,"test_dash_run","-s","init","stop"]),
+
+    {["a"],["b"]} =
+        run_dash_test(["-run",?MODULE,"test_dash_run","a","--","b","-s","init","stop"]),
+
+    %% Test error conditions
+    ?assertNotEqual(
+       nomatch,
+       string:find(run_dash_test(["-run","a"]),
+                   "Error! Failed to load module 'a' because it cannot be found.")),
+
+    ?assertNotEqual(
+       nomatch,
+       string:find(run_dash_test(["-run",?MODULE]),
+                   "Error! init_SUITE:start/0 is not exported.")),
+
+    ?assertNotEqual(
+       nomatch,
+       string:find(run_dash_test(["-run",?MODULE,"a"]),
+                   "Error! init_SUITE:a/0 is not exported.")),
+
+    ok.
+
+test_dash_run() ->
+    test_dash_run(undefined).
+test_dash_run(Args) ->
+    io:format("~p.",[{Args, init:get_plain_arguments(), erlang:system_info(emu_args)}]),
+    ok.
+
+dash_s(_Config) ->
+
+    {undefined,[]} =
+        run_dash_test(["-s",?MODULE,"test_dash_run","-s","init","stop"]),
+
+    {[a],["b"]} =
+        run_dash_test(["-s",?MODULE,"test_dash_run","a","--","b","-s","init","stop"]),
+
+    %% Test error conditions
+    ?assertNotEqual(
+       nomatch,
+       string:find(run_dash_test(["-s","a"]),
+                   "Error! Failed to load module 'a' because it cannot be found.")),
+
+    ?assertNotEqual(
+       nomatch,
+       string:find(run_dash_test(["-s",?MODULE]),
+                   "Error! init_SUITE:start/0 is not exported.")),
+
+    ?assertNotEqual(
+       nomatch,
+       string:find(run_dash_test(["-s",?MODULE,"a"]),
+                   "Error! init_SUITE:a/0 is not exported.")),
+
+    ok.
+
+dash_extra(Config) ->
+    %% Test that arguments are passed correctly
+    {[]} = run_dash_extra_test([]),
+    {["a"]} = run_dash_extra_test(["a"]),
+    {["--help"]} = run_dash_extra_test(["--help"]),
+    {["-S","--"]} = run_dash_extra_test(["-S","--"]),
+    {["-extra","--"]} = run_dash_extra_test(["-extra","--"]),
+    {["-run"]} = run_dash_extra_test(["-run"]),
+    {["-args_file"]} = run_dash_extra_test(["-args_file"]),
+    {["+A","-1"]} = run_dash_extra_test(["+A","-1"]),
+    {["-s","init","stop"]} = run_dash_extra_test(["-s","init","stop"]),
+
+    %% Test that environment variables are handled correctly
+    {["b","c","d","a"]} =
+        run_dash_extra_test([{"ERL_AFLAGS","b"},{"ERL_FLAGS","c"},{"ERL_ZFLAGS","d"}],
+                            ["a"]),
+    {["c","d","+A","1","--","a"]} =
+        run_dash_extra_test([{"ERL_AFLAGS","-extra +A 1 --"},{"ERL_FLAGS","c"},{"ERL_ZFLAGS","d"}],
+                            ["a"]),
+    {["+A","a","+B","+C"]} =
+        run_dash_extra_test([{"ERL_AFLAGS","-extra +A"},
+                             {"ERL_FLAGS","-extra +B"},
+                             {"ERL_ZFLAGS","-extra +C"}],["a"]),
+
+    %% Test that arguments from -args_file work as they should
+    ArgsFile = filename:join(?config(priv_dir, Config),
+                             atom_to_list(?MODULE) ++ "_args_file.args"),
+    NestedArgsFile = filename:join(?config(priv_dir, Config),
+                             atom_to_list(?MODULE) ++ "_nexted_args_file.args"),
+    file:write_file(NestedArgsFile,"y -extra +Y"),
+
+    file:write_file(ArgsFile,["z -args_file ",NestedArgsFile," -extra +Z"]),
+
+    {["c","z","y","d",
+      %% -extra starts here
+      "a","+Y","+Z","b"]} =
+        run_dash_extra_test([{"ERL_FLAGS",["c -args_file ",ArgsFile," d -extra b"]}],["a"]),
+
+    ok.
+
+run_dash_extra_test(Args) ->
+    run_dash_extra_test([], Args).
+run_dash_extra_test(Prefix, Args) ->
+    run_dash_test(Prefix, ["-run", ?MODULE, "test_dash_extra", "-extra" | Args]).
+
+test_dash_extra() ->
+    AllArgs = {init:get_plain_arguments(), erlang:system_info(emu_args)},
+    io:format("~p.",[AllArgs]),
+    erlang:halt().
+
+
+run_dash_test(Args) ->
+    run_dash_test([],Args).
+run_dash_test(Env, Args) ->
+    [Exec | ExecArgs] = string:split(ct:get_progname()," ", all),
+    PortExec = os:find_executable(Exec),
+    PortArgs = ExecArgs ++ ["-pa",filename:dirname(code:which(?MODULE)),
+                            "-noshell" | Args],
+    PortEnv = [{"ERL_CRASH_DUMP_SECONDS","0"} |
+               [{K,lists:flatten(V)} || {K, V} <- Env]],
+    ct:log("Exec: ~p~nPortArgs: ~p~nPortEnv: ~p~n",[PortExec, PortArgs, PortEnv]),
+    Port =
+        open_port({spawn_executable, PortExec},
+                  [stderr_to_stdout,binary,out,in,hide,exit_status,
+                   {args, PortArgs}, {env, PortEnv}]),
+    receive
+        {Port,{exit_status,N}} ->
+            N
+    after 5000 ->
+            ct:fail({timeout, receive M -> M after 0 -> [] end})
+    end,
+    Res = unicode:characters_to_list(
+            iolist_to_binary(
+              (fun F() ->
+                       receive
+                           {Port,{data,Data}} ->
+                               [Data | F()]
+                       after 0 ->
+                               []
+                       end
+               end)())),
+    ct:log("Res: ~ts~n",[Res]),
+    maybe
+        {ok, Toks, _} ?= erl_scan:string(Res),
+        {ok, Tuple} ?= erl_parse:parse_term(Toks),
+        erlang:delete_element(tuple_size(Tuple), Tuple)
+    else
+        _ ->
+            Res
+    end.
+
 %% Misc. functions    
 
 args() ->
-- 
2.35.3

openSUSE Build Service is sponsored by