File 5751-Speedup-valgrind_beamasm_update-script.patch of Package erlang

From fb9f29805589bd1c6d277b76f53d71d6625cabaf Mon Sep 17 00:00:00 2001
From: Ildar Khizbulin <khizbulin@erlyvideo.org>
Date: Thu, 2 Mar 2023 15:41:43 +0300
Subject: [PATCH] Speedup valgrind_beamasm_update script

---
 scripts/valgrind_beamasm_update.escript | 114 +++++++++++++++---------
 1 file changed, 74 insertions(+), 40 deletions(-)

diff --git a/scripts/valgrind_beamasm_update.escript b/scripts/valgrind_beamasm_update.escript
index ae2dd0e170..5fa640426c 100755
--- a/scripts/valgrind_beamasm_update.escript
+++ b/scripts/valgrind_beamasm_update.escript
@@ -3,79 +3,113 @@
 -mode(compile).
 
 main([VGFile,PerfFile]) ->
+    ets:new(perf, [ordered_set, {keypos,1}, named_table]),
     {ok, Perf} = file:read_file(PerfFile),
-    {ok, VG} = file:read_file(VGFile),
-    file:write_file(VGFile,update_vg(VG, parse_perf(Perf))).
+    {ok, VGIo} = file:open(VGFile, [read,binary]),
+    parse_perf(Perf),
+    case update_vg(VGIo) of
+        {ok, Out} ->
+            file:write_file(VGFile, Out);
+        {error, Error} ->
+            io:format(standard_error, "Error ~p", [Error]),
+            exit(1)
+    end.
 
 parse_perf(Perf) ->
     %% Example: 0x409b1c0 84 $global::arith_compare_shared
-    lists:foldl(
-      fun(<<>>, Acc) ->
-              Acc;
-         (Line, Acc) ->
+    lists:foreach(
+      fun(<<>>) ->
+              ok;
+         (Line) ->
               [<<"0x",Base/binary>>, Size, Name] = string:split(Line," ",all),
-              Acc#{ binary_to_integer(Base, 16) =>
-                        {binary_to_integer(Size, 16), Name}}
-      end,#{},string:split(Perf,"\n",all)).
+              Start = binary_to_integer(Base, 16),
+              End = Start + binary_to_integer(Size, 16),
+              ets:insert(perf, [{Start, End, Name}])
+      end,string:split(Perf,"\n",all)).
+
+update_vg(VGIo) ->
+    {ok, RegularPattern} = re:compile("(?:by|at) 0x([0-9A-F]+): (\\?\\?\\?)"),
+    {ok, XmlPattern} = re:compile("(<ip>0x([0-9A-F]+)</ip>)"),
+    update_vg(VGIo, RegularPattern, XmlPattern, [], #{}).
 
+update_vg(VGIo, RegularPattern, XmlPattern, Acc, AddrCache) ->
+    case io:get_line(VGIo, "") of
+        eof ->
+            {ok, lists:reverse(Acc)};
+        {error, _} = Error ->
+            Error;
+        Line ->
+            {Line1, AddrCache1} = update_vg0(Line, RegularPattern, XmlPattern, AddrCache),
+            update_vg(VGIo, RegularPattern, XmlPattern, [Line1|Acc], AddrCache1)
+    end.
 
-update_vg(VG, Perf) ->
+update_vg0(Line, RegularPattern, XmlPattern, AddrCache) ->
     %% Check if regular log file
-    case re:run(VG,"(?:by|at) 0x([0-9A-F]+): (\\?\\?\\?)",[global]) of
+    case re:run(Line,RegularPattern,[global]) of
         {match, Matches} ->
             lists:foldl(
-              fun(Match, File) ->
+              fun(Match, {File, Cache}) ->
                       [_,Base, Replace] = Match,
-                      case find_replacement(binary_to_integer(binary:part(VG,Base),16), Perf) of
-                          undefined ->
-                              File;
-                          Replacement ->
-                              replace(File,Replace,Replacement)
+                      case find_replacement_cached(binary_to_integer(binary:part(Line,Base),16), Cache) of
+                          {undefined, Cache1} ->
+                              {File, Cache1};
+                          {Replacement, Cache1} ->
+                              {replace(File,Replace,Replacement), Cache1}
                       end
-              end, VG,
+              end, {Line, AddrCache},
               %% Run replacements in reverse in order to not invalidate
               %% the positions as we update the contents.
               lists:reverse(Matches));
         _ ->
             %% Check if xml log file
-            case re:run(VG,"(<ip>0x([0-9A-F]+)</ip>)",[global]) of
+            case re:run(Line,XmlPattern,[global]) of
                 {match, Matches} ->
                     lists:foldl(
-                      fun(Match, File) ->
+                      fun(Match, {File, Cache}) ->
                               [_,Replace,Base] = Match,
-                              case find_replacement(binary_to_integer(binary:part(VG,Base),16), Perf) of
-                                  undefined ->
-                                      File;
-                                  Replacement ->
-                                      Xml = ["<ip>0x",binary:part(VG,Base),"</ip>\n"
+                              case find_replacement_cached(binary_to_integer(binary:part(Line,Base),16), Cache) of
+                                  {undefined, Cache1} ->
+                                      {File, Cache1};
+                                  {Replacement, Cache1} ->
+                                      Xml = ["<ip>0x",binary:part(Line,Base),"</ip>\n"
                                              "      <obj>JIT code</obj>\n"
                                              "      <fn>",Replacement,"</fn>\n"
                                              "      <dir></dir>\n"
                                              "      <file></file>\n"
                                              "      <line></line>"],
-                                      replace(File,Replace,Xml)
+                                      {replace(File,Replace,Xml), Cache1}
                               end
-                      end, VG,
+                      end, {Line, AddrCache},
                       %% Run replacements in reverse in order to not invalidate
                       %% the positions as we update the contents.
                       lists:reverse(Matches));
                 _ ->
-                    VG
+                    {Line, AddrCache}
             end
     end.
 
-find_replacement(Addr, Perf) when is_map(Perf) ->
-    find_replacement(Addr, maps:iterator(Perf));
-find_replacement(Addr, Iter) ->
-    case maps:next(Iter) of
-        {Base,{Size,Str},Next} ->
-            if Base =< Addr andalso Addr < Base + Size ->
-                    [Str,"+",integer_to_list(Addr - Base, 16)];
-               true ->
-                    find_replacement(Addr,Next)
-            end;
-        none ->
-            undefined
+find_replacement_cached(Addr, Cache) ->
+    case Cache of
+        #{Addr := Result} ->
+            {Result, Cache};
+        _ ->
+            Result = find_replacement(Addr),
+            {Result, Cache#{Addr => Result}}
+    end.
+
+
+find_replacement(Addr) ->
+    MatchSpec = [{{'$1','$2','$3'},
+      [{'andalso',{'>=', Addr,'$1'},
+                {'=<', Addr,'$2'}}],
+      [{{'$1','$3'}}]}],
+    case ets:select(perf, MatchSpec, 1) of
+        [] ->
+            undefined;
+        '$end_of_table' ->
+            undefined;
+        {[{Start, Name}], _} ->
+            [Name,"+",integer_to_list(Addr - Start, 16)]
     end.
 
 replace(Bin,{Start,Len},What) ->
-- 
2.35.3

openSUSE Build Service is sponsored by