File 1002-escript-direct-all-io-format-2-calls-to-standard_err.patch of Package erlang

From 0d67f92d35af61a7a8da504bdd9e2212ac9315ad Mon Sep 17 00:00:00 2001
From: Mikael Pettersson <mikpelinux@gmail.com>
Date: Sat, 12 Sep 2020 18:28:01 +0200
Subject: [PATCH 2/9] escript: direct all io:format/2 calls to standard_error

they are all error or debugging messages
---
 lib/stdlib/src/escript.erl | 20 ++++++++++----------
 1 file changed, 10 insertions(+), 10 deletions(-)

diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl
index d0129095ff..50f774c5fc 100644
--- a/lib/stdlib/src/escript.erl
+++ b/lib/stdlib/src/escript.erl
@@ -276,7 +276,7 @@ start(EscriptOptions) ->
             [File|Args] ->
                 parse_and_run(File, Args, EscriptOptions);
             [] ->
-                io:format("escript: Missing filename\n", []),
+                io:format(standard_error, "escript: Missing filename\n", []),
                 my_halt(127)
         end
     catch
@@ -635,7 +635,7 @@ parse_source(S, File, Fd, StartLine, HeaderSz, CheckOnly) ->
             ok = file:close(Fd),
 	    check_source(S3, CheckOnly);
 	{error, Reason} ->
-	    io:format("escript: ~tp\n", [Reason]),
+	    io:format(standard_error, "escript: ~tp\n", [Reason]),
 	    fatal("Preprocessor error")
     end.
 
@@ -693,7 +693,7 @@ epp_parse_file(Epp, S, Forms) ->
     epp_parse_file2(Epp, S, Forms, Parsed).
 
 epp_parse_file2(Epp, S, Forms, Parsed) ->
-    %% io:format("~p\n", [Parsed]),
+    %% io:format(standard_error, "~p\n", [Parsed]),
     case Parsed of
         {ok, Form} ->
             case Form of
@@ -707,7 +707,7 @@ epp_parse_file2(Epp, S, Forms, Parsed) ->
                             epp_parse_file(Epp, S2, [Form | Forms]);
                         true ->
                             Args = lists:flatten(io_lib:format("illegal mode attribute: ~p", [NewMode])),
-                            io:format("~ts:~w ~s\n", [S#state.file,Ln,Args]),
+                            io:format(standard_error, "~ts:~w ~s\n", [S#state.file,Ln,Args]),
                             Error = {error,{Ln,erl_parse,Args}},
                             Nerrs= S#state.n_errors + 1,
                             epp_parse_file(Epp, S2#state{n_errors = Nerrs}, [Error | Forms])
@@ -723,7 +723,7 @@ epp_parse_file2(Epp, S, Forms, Parsed) ->
                     epp_parse_file(Epp, S, [Form | Forms])
             end;
         {error,{Ln,Mod,Args}} = Form ->
-            io:format("~ts:~w: ~ts\n",
+            io:format(standard_error, "~ts:~w: ~ts\n",
                       [S#state.file,Ln,Mod:format_error(Args)]),
             epp_parse_file(Epp, S#state{n_errors = S#state.n_errors + 1}, [Form | Forms]);
         {eof, LastLine} ->
@@ -802,10 +802,10 @@ report_errors(Errors) ->
                   Errors).
 
 list_errors(F, [{Line,Mod,E}|Es]) ->
-    io:format("~ts:~w: ~ts\n", [F,Line,Mod:format_error(E)]),
+    io:format(standard_error, "~ts:~w: ~ts\n", [F,Line,Mod:format_error(E)]),
     list_errors(F, Es);
 list_errors(F, [{Mod,E}|Es]) ->
-    io:format("~ts: ~ts\n", [F,Mod:format_error(E)]),
+    io:format(standard_error, "~ts: ~ts\n", [F,Mod:format_error(E)]),
     list_errors(F, Es);
 list_errors(_F, []) -> ok.
 
@@ -842,7 +842,7 @@ parse_to_dict([], Dict) ->
 code_handler(local, [file], _, File) ->
     File;
 code_handler(Name, Args, Dict, File) ->
-    %%io:format("code handler=~p~n",[{Name, Args}]),
+    %%io:format(standard_error, "code handler=~p~n",[{Name, Args}]),
     Arity = length(Args),
     case dict:find({local,Name,Arity}, Dict) of
         {ok, Cs} ->
@@ -856,10 +856,10 @@ code_handler(Name, Args, Dict, File) ->
         error ->
             case dict:find({remote,{Name,Arity}}, Dict) of
                 {ok, Mod} ->
-                    %% io:format("Calling:~p~n",[{Mod,Name,Args}]),
+                    %% io:format(standard_error, "Calling:~p~n",[{Mod,Name,Args}]),
                     apply(Mod, Name, Args);
                 error ->
-                    io:format("Script does not export ~w/~w\n", [Name,Arity]),
+                    io:format(standard_error, "Script does not export ~w/~w\n", [Name,Arity]),
                     my_halt(127)
             end
     end.
-- 
2.26.2

openSUSE Build Service is sponsored by