File 2203-scripts-diffable-Use-the-diffable-compiler-option.patch of Package erlang

From e5aaeb8ebc59c6e7999b0e41a17ea1e5ad873ed5 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Tue, 23 Oct 2018 09:19:37 +0200
Subject: [PATCH 3/4] scripts/diffable: Use the diffable compiler option

Now that the compiler has a `diffable` option, use it for a slight
speed up.
---
 scripts/diffable | 153 +++++++++++--------------------------------------------
 1 file changed, 29 insertions(+), 124 deletions(-)

diff --git a/scripts/diffable b/scripts/diffable
index 66b50d0499..28dc71c69e 100755
--- a/scripts/diffable
+++ b/scripts/diffable
@@ -3,7 +3,8 @@
 -mode(compile).
 
 main(Args0) ->
-    {Args,Opts} = opts(Args0, #{format=>asm,no_compile=>false}),
+    DefOpts = #{format=>asm,no_compile=>false,legacy=>false},
+    {Args,Opts} = opts(Args0, DefOpts),
     case Args of
 	[OutDir] ->
 	    do_compile(OutDir, Opts);
@@ -15,6 +16,7 @@ usage() ->
     S = "usage: otp-diffable-asm [OPTION] DIRECTORY\n\n"
         "Options:\n"
         "  --asm          Output to .S files (default)\n"
+        "  --legacy-asm   Output to legacy .S files\n"
         "  --dis          Output to .dis files\n"
         "  --no-compile   Disassemble from BEAM files (use with --dis)\n"
         "\n"
@@ -23,6 +25,8 @@ usage() ->
         "Compile some applications from OTP (more than 700 modules) to either\n"
         ".S files or .dis files. The files are massaged to make them diff-friendly.\n"
         "\n"
+        "The --legacy-asm options forces the output file to be in Latin1 encoding\n"
+        "and adds a latin1 encoding comment to the first line of the file.\n"
         "EXAMPLES\n"
         "\n"
         "This example shows how the effectiveness of a compiler \n"
@@ -54,9 +58,11 @@ opt("asm", Opts) ->
     Opts#{format:=asm};
 opt("dis", Opts) ->
     Opts#{format:=dis};
+opt("legacy-asm", Opts) ->
+    Opts#{format:=asm,legacy:=true};
 opt("no-compile", Opts) ->
     Opts#{format:=dis,no_compile:=true};
-opt(Opt, Opts) ->
+opt(Opt, _Opts) ->
     io:format("Uknown option: --~ts\n\n", [Opt]),
     usage().
 
@@ -204,109 +210,33 @@ get_beams([]) -> [].
 %%% Generate renumbered .S files.
 %%%
 
-compile_to_asm_fun(#{outdir:=OutDir}) ->
+compile_to_asm_fun(#{outdir:=OutDir}=Opts) ->
     fun(File) ->
-            compile_to_asm(File, OutDir)
+            Legacy = map_get(legacy, Opts),
+            compile_to_asm(File, OutDir, Legacy)
     end.
 
-compile_to_asm({File,Opts}, OutDir) ->
-    case compile:file(File, [to_asm,binary,report_errors|Opts]) of
+compile_to_asm({File,Opts}, OutDir, Legacy) ->
+    case compile:file(File, [diffable,{outdir,OutDir},report_errors|Opts]) of
+        {ok,_Mod} ->
+            case Legacy of
+                true ->
+                    legacy_asm(OutDir, File);
+                false ->
+                    ok
+            end;
         error ->
-            error;
-        {ok,Mod,Asm0} ->
-            {ok,Asm1} = beam_a:module(Asm0, []),
-            Asm2 = renumber_asm(Asm1),
-            {ok,Asm} = beam_z:module(Asm2, []),
-            print_asm(Mod, OutDir, Asm)
+            error
     end.
 
-print_asm(Mod, OutDir, Asm) ->
-    S = atom_to_list(Mod) ++ ".S",
-    Name = filename:join(OutDir, S),
-    {ok,Fd} = file:open(Name, [write,raw,delayed_write]),
-    ok = beam_listing(Fd, Asm),
-    ok = file:close(Fd).
-
-renumber_asm({Mod,Exp,Attr,Fs0,NumLabels}) ->
-    EntryLabels = maps:from_list(entry_labels(Fs0)),
-    Fs = [fix_func(F, EntryLabels) || F <- Fs0],
-    {Mod,Exp,Attr,Fs,NumLabels}.
-
-entry_labels(Fs) ->
-    [{Entry,{Name,Arity}} || {function,Name,Arity,Entry,_} <- Fs].
-
-fix_func({function,Name,Arity,Entry0,Is0}, LabelMap0) ->
-    Entry = maps:get(Entry0, LabelMap0),
-    LabelMap = label_map(Is0, 1, LabelMap0),
-    Is = replace(Is0, [], LabelMap),
-    {function,Name,Arity,Entry,Is}.
-
-label_map([{label,Old}|Is], New, Map) ->
-    case maps:is_key(Old, Map) of
-        false ->
-            label_map(Is, New+1, Map#{Old=>New});
-        true ->
-            label_map(Is, New, Map)
-    end;
-label_map([_|Is], New, Map) ->
-    label_map(Is, New, Map);
-label_map([], _New, Map) ->
-    Map.
-
-replace([{label,Lbl}|Is], Acc, D) ->
-    replace(Is, [{label,label(Lbl, D)}|Acc], D);
-replace([{test,Test,{f,Lbl},Ops}|Is], Acc, D) ->
-    replace(Is, [{test,Test,{f,label(Lbl, D)},Ops}|Acc], D);
-replace([{test,Test,{f,Lbl},Live,Ops,Dst}|Is], Acc, D) ->
-    replace(Is, [{test,Test,{f,label(Lbl, D)},Live,Ops,Dst}|Acc], D);
-replace([{select,I,R,{f,Fail0},Vls0}|Is], Acc, D) ->
-    Vls = lists:map(fun ({f,L}) -> {f,label(L, D)};
-			(Other) -> Other
-		    end, Vls0),
-    Fail = label(Fail0, D),
-    replace(Is, [{select,I,R,{f,Fail},Vls}|Acc], D);
-replace([{'try',R,{f,Lbl}}|Is], Acc, D) ->
-    replace(Is, [{'try',R,{f,label(Lbl, D)}}|Acc], D);
-replace([{'catch',R,{f,Lbl}}|Is], Acc, D) ->
-    replace(Is, [{'catch',R,{f,label(Lbl, D)}}|Acc], D);
-replace([{jump,{f,Lbl}}|Is], Acc, D) ->
-    replace(Is, [{jump,{f,label(Lbl, D)}}|Acc], D);
-replace([{loop_rec,{f,Lbl},R}|Is], Acc, D) ->
-    replace(Is, [{loop_rec,{f,label(Lbl, D)},R}|Acc], D);
-replace([{loop_rec_end,{f,Lbl}}|Is], Acc, D) ->
-    replace(Is, [{loop_rec_end,{f,label(Lbl, D)}}|Acc], D);
-replace([{wait,{f,Lbl}}|Is], Acc, D) ->
-    replace(Is, [{wait,{f,label(Lbl, D)}}|Acc], D);
-replace([{wait_timeout,{f,Lbl},To}|Is], Acc, D) ->
-    replace(Is, [{wait_timeout,{f,label(Lbl, D)},To}|Acc], D);
-replace([{bif,Name,{f,Lbl},As,R}|Is], Acc, D) when Lbl =/= 0 ->
-    replace(Is, [{bif,Name,{f,label(Lbl, D)},As,R}|Acc], D);
-replace([{gc_bif,Name,{f,Lbl},Live,As,R}|Is], Acc, D) when Lbl =/= 0 ->
-    replace(Is, [{gc_bif,Name,{f,label(Lbl, D)},Live,As,R}|Acc], D);
-replace([{call,Ar,{f,Lbl}}|Is], Acc, D) ->
-    replace(Is, [{call,Ar,{f,label(Lbl,D)}}|Acc], D);
-replace([{make_fun2,{f,Lbl},U1,U2,U3}|Is], Acc, D) ->
-    replace(Is, [{make_fun2,{f,label(Lbl, D)},U1,U2,U3}|Acc], D);
-replace([{bs_init,{f,Lbl},Info,Live,Ss,Dst}|Is], Acc, D) when Lbl =/= 0 ->
-    replace(Is, [{bs_init,{f,label(Lbl, D)},Info,Live,Ss,Dst}|Acc], D);
-replace([{bs_put,{f,Lbl},Info,Ss}|Is], Acc, D) when Lbl =/= 0 ->
-    replace(Is, [{bs_put,{f,label(Lbl, D)},Info,Ss}|Acc], D);
-replace([{put_map=I,{f,Lbl},Op,Src,Dst,Live,List}|Is], Acc, D)
-  when Lbl =/= 0 ->
-    replace(Is, [{I,{f,label(Lbl, D)},Op,Src,Dst,Live,List}|Acc], D);
-replace([{get_map_elements=I,{f,Lbl},Src,List}|Is], Acc, D) when Lbl =/= 0 ->
-    replace(Is, [{I,{f,label(Lbl, D)},Src,List}|Acc], D);
-replace([{recv_mark=I,{f,Lbl}}|Is], Acc, D) ->
-    replace(Is, [{I,{f,label(Lbl, D)}}|Acc], D);
-replace([{recv_set=I,{f,Lbl}}|Is], Acc, D) ->
-    replace(Is, [{I,{f,label(Lbl, D)}}|Acc], D);
-replace([I|Is], Acc, D) ->
-    replace(Is, [I|Acc], D);
-replace([], Acc, _) ->
-    lists:reverse(Acc).
-
-label(Old, D) when is_integer(Old) ->
-    maps:get(Old, D).
+legacy_asm(OutDir, Source) ->
+    ModName = filename:rootname(filename:basename(Source)),
+    File = filename:join(OutDir, ModName),
+    AsmFile = File ++ ".S",
+    {ok,Asm0} = file:read_file(AsmFile),
+    Asm1 = unicode:characters_to_binary(Asm0, utf8, latin1),
+    Asm = [<<"%% -*- encoding:latin-1 -*-\n">>|Asm1],
+    ok = file:write_file(AsmFile, Asm).
 
 %%%
 %%% Compile and disassemble the loaded code.
@@ -614,28 +544,3 @@ p_run_loop(Test, List, N, Refs0, Errors0) ->
 	    Refs = Refs0 -- [Ref],
 	    p_run_loop(Test, List, N, Refs, Errors)
     end.
-
-%%%
-%%% Borrowed from beam_listing and tweaked.
-%%%
-
-beam_listing(Stream, {Mod,Exp,Attr,Code,NumLabels}) ->
-    Head = ["%% -*- encoding:latin-1 -*-\n",
-            io_lib:format("{module, ~p}.  %% version = ~w\n",
-                          [Mod, beam_opcodes:format_number()]),
-            io_lib:format("\n{exports, ~p}.\n", [Exp]),
-            io_lib:format("\n{attributes, ~p}.\n", [Attr]),
-            io_lib:format("\n{labels, ~p}.\n", [NumLabels])],
-    ok = file:write(Stream, Head),
-    lists:foreach(
-      fun ({function,Name,Arity,Entry,Asm}) ->
-              S = [io_lib:format("\n\n{function, ~w, ~w, ~w}.\n",
-                                 [Name,Arity,Entry])|format_asm(Asm)],
-              ok = file:write(Stream, S)
-      end, Code).
-
-format_asm([{label,_}=I|Is]) ->
-    [io_lib:format("  ~p", [I]),".\n"|format_asm(Is)];
-format_asm([I|Is]) ->
-    [io_lib:format("    ~p", [I]),".\n"|format_asm(Is)];
-format_asm([]) -> [].
-- 
2.16.4

openSUSE Build Service is sponsored by