File 1821-init-Introduce-S-flag.patch of Package erlang

From d4e90c4d00ee517ee2803b6253639600d7c5a2a7 Mon Sep 17 00:00:00 2001
From: Johannes Christ <jc@jchri.st>
Date: Tue, 4 Jul 2023 11:20:43 +0200
Subject: [PATCH] init: Introduce -S flag

The flag works similarly to `-s` and `-run`, except that:
- Additional command line arguments starting with a hyphen will be
  passed to the invoked script as well, whilst with `-s` and `-run`
  these arguments will be passed to the runtime system.
- Command-line arguments will be passed directly to the function,
  without having to call `init:get_plain_arguments`.
- Scripts that make use of this option only need to define a function of
  arity one, as passing no arguments will result in a call like
  `func([])` as opposed to `func()`, which would be the behaviour of the
  existing options.

The documentation for the existing `-s` and `-run` options was updated
to mention that they will not forward arguments starting with a hyphen
to the specified function, to prevent surprises when using `argparse` or
other option parser libraries.
---
 erts/doc/src/erl_cmd.xml    | 11 ++++++
 erts/doc/src/init.xml       | 32 +++++++++++++++++
 erts/preloaded/src/init.erl | 68 +++++++++++++++++++++++++------------
 3 files changed, 89 insertions(+), 22 deletions(-)

diff --git a/erts/doc/src/erl_cmd.xml b/erts/doc/src/erl_cmd.xml
index 8a2337c5cd..5bd565b80c 100644
--- a/erts/doc/src/erl_cmd.xml
+++ b/erts/doc/src/erl_cmd.xml
@@ -627,6 +627,17 @@ $ <input>erl \
           slave node on a remote host; see
           <seeerl marker="stdlib:slave"><c>slave(3)</c></seeerl>.</p>
       </item>
+      <tag><c><![CDATA[-S Mod [Func [Arg1, Arg2, ...]]]]></c> (init
+        flag)</tag>
+      <item>
+        <p>Makes <c><![CDATA[init]]></c> call the specified function.
+          <c><![CDATA[Func]]></c> defaults to <c><![CDATA[start]]></c>.
+          The function is assumed to be of arity 1, taking the list
+          <c><![CDATA[[Arg1,Arg2,...]]]></c> as argument, or an empty list
+          if no arguments are passed. All further arguments occurring after
+          this option are passed to the specified function as strings.
+          See <seeerl marker="init"> <c>init(3)</c></seeerl>.</p>
+      </item>
       <tag><c><![CDATA[-run Mod [Func [Arg1, Arg2, ...]]]]></c> (init
         flag)</tag>
       <item>
diff --git a/erts/doc/src/init.xml b/erts/doc/src/init.xml
index 2d6b22a826..0c358ba8c7 100644
--- a/erts/doc/src/init.xml
+++ b/erts/doc/src/init.xml
@@ -310,6 +310,28 @@ BF</pre>
           <seemfa marker="#get_plain_arguments/0">
           <c>get_plain_arguments/0</c></seemfa>.</p>
       </item>
+      <tag><c>-S Mod [Func [Arg1, Arg2, ...]]</c></tag>
+      <item>
+        <p>Evaluates the specified function call during system
+          initialization. <c>Func</c> defaults to <c>start</c>. If no
+          arguments are provided, the function is assumed to be of arity
+          0. Otherwise it is assumed to be of arity 1, taking the list
+          <c>[Arg1,Arg2,...]</c> as argument. All arguments are passed
+          as strings. If an exception is raised, Erlang stops with an
+          error message.</p>
+        <p>Example:</p>
+        <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
+          to the called function.</p>
+        <p>The function is executed sequentially in an initialization
+          process, which then terminates normally and passes control to
+          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>
+      </item>
       <tag><c>-run Mod [Func [Arg1, Arg2, ...]]</c></tag>
       <item>
         <p>Evaluates the specified function call during system
@@ -333,6 +355,10 @@ foo:bar(["baz", "1", "2"]).</code>
           the user. This means that a <c>-run</c> call that does not
           return blocks further processing; to avoid this, use
           some variant of <c>spawn</c> in such cases.</p>
+        <note><p>This flag will not forward arguments beginning with
+          a hyphen (-) to the specified function, as these will be
+          interpreted as flags to the runtime. If the function uses
+          flags in this form, it is advised to use <c>-S</c> instead.</p></note>
       </item>
       <tag><c>-s Mod [Func [Arg1, Arg2, ...]]</c></tag>
       <item>
@@ -359,6 +385,12 @@ foo:bar([baz, '1', '2']).</code>
           some variant of <c>spawn</c> in such cases.</p>
         <p>Because of the limited length of atoms, it is recommended to
           use <c>-run</c> instead.</p>
+        <note><p>This flag will not forward arguments beginning with
+          a hyphen (-) to the specified function, as these will be
+          interpreted as flags to the runtime. If the function uses
+          flags in this form, it is advised to use <c>-S</c> instead,
+          with the additional caveat that arguments are passed as strings
+          instead of atoms.</p></note>
       </item>
     </taglist>
   </section>
diff --git a/erts/preloaded/src/init.erl b/erts/preloaded/src/init.erl
index 1f7ef28085..1b9af02591 100644
--- a/erts/preloaded/src/init.erl
+++ b/erts/preloaded/src/init.erl
@@ -39,6 +39,7 @@
 %%        -pz Path+      : Add my own paths last.
 %%        -run           : Start own processes.
 %%        -s             : Start own processes.
+%%        -S             : Start own processes and terminate further option processing.
 %% 
 %% Experimental flags:
 %%        -profile_boot    : Use an 'eprof light' to profile boot sequence
@@ -256,25 +257,40 @@ boot(BootArgs) ->
     register(init, self()),
     process_flag(trap_exit, true),
 
-    {Start0,Flags,Args} = parse_boot_args(BootArgs),
+    {Start,Flags,Args} = parse_boot_args(BootArgs),
     %% We don't get to profile parsing of BootArgs
     case b2a(get_flag(profile_boot, Flags, false)) of
         false -> ok;
         true  -> debug_profile_start()
     end,
-    Start = map(fun prepare_run_args/1, Start0),
     boot(Start, Flags, Args).
 
-prepare_run_args({eval, [Expr]}) ->
-    {eval,Expr};
-prepare_run_args({_, L=[]}) ->
-    bs2as(L);
-prepare_run_args({_, L=[_]}) ->
-    bs2as(L);
-prepare_run_args({s, [M,F|Args]}) ->
-    [b2a(M), b2a(F) | bs2as(Args)];
-prepare_run_args({run, [M,F|Args]}) ->
-    [b2a(M), b2a(F) | bs2ss(Args)].
+fold_eval_args([Expr]) -> Expr;
+fold_eval_args(Exprs) -> Exprs.
+
+%% Ensure that when no arguments were explicitly passed on the command line,
+%% an empty arguments list will be passed to the function to be applied.
+interpolate_empty_mfa_args({M, F, []}) -> {M, F, [[]]};
+interpolate_empty_mfa_args({_M, _F, [_Args]} = MFA) -> MFA.
+
+-spec run_args_to_mfa([binary()]) -> {atom(), atom(), [] | [nonempty_list(binary())]} | no_return().
+run_args_to_mfa([]) ->
+    erlang:display_string(
+      "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);
+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]}.
+
+%% Convert -run / -s / -S arguments to startup instructions, such that
+%% no instructions are emitted if no arguments follow the flag, otherwise,
+%% an `{apply, M, F, A}' instruction is.
+run_args_to_start_instructions([], _Converter) -> [];
+run_args_to_start_instructions(Args, Converter) ->
+    {M, F, A} = run_args_to_mfa(Args),
+    [{apply, M, F, map(Converter, A)}].
 
 b2a(Bin) when is_binary(Bin) ->
     list_to_atom(b2s(Bin));
@@ -1201,15 +1217,10 @@ start_it({eval,Bin}) ->
             erlang:display_string(binary_to_list(iolist_to_binary(Message))),
             erlang:raise(E,R,ST)
     end;
-start_it([M|FA]) ->
+start_it({apply,M,F,Args}) ->
     case code:ensure_loaded(M) of
         {module, M} ->
-            case FA of
-                []       -> M:start();
-                [F]      -> M:F();
-                [F|Args] -> M:F(Args)	% Args is a list
-            end;
-
+            apply(M, F, Args);
         {error, Reason} ->
             Message = [explain_ensure_loaded_error(M, Reason), <<"\r\n\r\n">>],
             erlang:display_string(binary_to_list(iolist_to_binary(Message))),
@@ -1288,6 +1299,7 @@ timer(T) ->
 %% --------------------------------------------------------
 %% Parse the command line arguments and extract things to start, flags
 %% and other arguments. We keep the relative of the groups.
+%% Returns a triplet in the form `{Start, Flags, Args}':
 %% --------------------------------------------------------
 
 parse_boot_args(Args) ->
@@ -1299,13 +1311,23 @@ parse_boot_args([B|Bs], Ss, Fs, As) ->
 	    {reverse(Ss),reverse(Fs),lists:reverse(As, Bs)}; % BIF
 	start_arg ->
 	    {S,Rest} = get_args(Bs, []),
-	    parse_boot_args(Rest, [{s, S}|Ss], Fs, As);
+            Instructions = run_args_to_start_instructions(S, fun bs2as/1),
+            parse_boot_args(Rest, Instructions ++ Ss, Fs, As);
 	start_arg2 ->
 	    {S,Rest} = get_args(Bs, []),
-	    parse_boot_args(Rest, [{run, S}|Ss], Fs, As);
+            Instructions = run_args_to_start_instructions(S, fun bs2ss/1),
+            parse_boot_args(Rest, Instructions ++ Ss, Fs, As);
+	ending_start_arg ->
+            {S,Rest} = get_args(Bs, []),
+            %% 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),[]};
 	eval_arg ->
 	    {Expr,Rest} = get_args(Bs, []),
-	    parse_boot_args(Rest, [{eval, Expr}|Ss], Fs, As);
+            parse_boot_args(Rest, [{eval, fold_eval_args(Expr)} | Ss], Fs, As);
 	{flag,A} ->
 	    {F,Rest} = get_args(Bs, []),
 	    Fl = {A,F},
@@ -1321,6 +1343,7 @@ parse_boot_args([], Start, Flags, 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)};
@@ -1333,6 +1356,7 @@ get_args([B|Bs], As) ->
 	start_arg2 -> {reverse(As), [B|Bs]};
 	eval_arg -> {reverse(As), [B|Bs]};
 	end_args -> {reverse(As), Bs};
+	ending_start_arg -> {reverse(As), [B|Bs]};
 	{flag,_} -> {reverse(As), [B|Bs]};
 	arg ->
 	    get_args(Bs, [B|As])
-- 
2.35.3

openSUSE Build Service is sponsored by