File 0868-fprof-Fix-conversion-of-pid-port-ref-funs-in-maps.patch of Package erlang

From 3e07e0e7c3d35e5d08137bdbf0553547c669b6fa Mon Sep 17 00:00:00 2001
From: Rickard Green <rickard@erlang.org>
Date: Fri, 21 Feb 2020 18:37:13 +0100
Subject: [PATCH] fprof: Fix conversion of pid, port, ref, funs in maps

---
 lib/tools/src/fprof.erl        |  2 ++
 lib/tools/test/fprof_SUITE.erl | 33 +++++++++++++++++++++++++++++++--
 2 files changed, 33 insertions(+), 2 deletions(-)

diff --git a/lib/tools/src/fprof.erl b/lib/tools/src/fprof.erl
index 36d4828861..369fbb2d42 100644
--- a/lib/tools/src/fprof.erl
+++ b/lib/tools/src/fprof.erl
@@ -2782,6 +2782,8 @@ parsify({A, B, C}) ->
     {parsify(A), parsify(B), parsify(C)};
 parsify(Tuple) when is_tuple(Tuple) ->
     list_to_tuple(parsify(tuple_to_list(Tuple)));
+parsify(Map) when is_map(Map) ->
+    maps:from_list(parsify(maps:to_list(Map)));
 parsify(Pid) when is_pid(Pid) ->
     erlang:pid_to_list(Pid);
 parsify(Port) when is_port(Port) ->
diff --git a/lib/tools/test/fprof_SUITE.erl b/lib/tools/test/fprof_SUITE.erl
index ae0e7253ad..cdb207c1e2 100644
--- a/lib/tools/test/fprof_SUITE.erl
+++ b/lib/tools/test/fprof_SUITE.erl
@@ -27,7 +27,7 @@
 %% Test suites
 -export([stack_seq/1, tail_seq/1, create_file_slow/1, spawn_simple/1,
          imm_tail_seq/1, imm_create_file_slow/1, imm_compile/1,
-         cpu_create_file_slow/1]).
+         cpu_create_file_slow/1, parsify_maps/1]).
 
 %% Other exports
 -export([create_file_slow/2]).
@@ -59,7 +59,7 @@ all() ->
         false ->
             [stack_seq, tail_seq, create_file_slow, spawn_simple,
              imm_tail_seq, imm_create_file_slow, imm_compile,
-             cpu_create_file_slow]
+             cpu_create_file_slow, parsify_maps]
     end.
 
 
@@ -532,6 +532,34 @@ unicode(Config) when is_list(Config) ->
     end,
     TestResult.
 
+parsify_maps(Config) when is_list(Config) ->
+    Pid = self(),
+    Ref = make_ref(),
+    Port = hd(erlang:ports()),
+    Fun = fun () -> ok end,
+    M = #{pid => Pid, Pid => pid,
+          ref => Ref, Ref => ref,
+          port => Port, Port => port,
+          a_fun => Fun, Fun => a_fun},
+    io:format("M = ~p~n", [M]),
+    L = [{tuple, M}, M, #{my_map => M, M => my_map}],
+    PL = fprof:parsify(L),
+    [{tuple, PM}, PM, PMap] = PL,
+    #{my_map := PM, PM := my_map} = PMap,
+    io:format("PM = ~p~n", [PM]),
+    LPid = pid_to_list(Pid),
+    LRef = ref_to_list(Ref),
+    LPort = port_to_list(Port),
+    LFun = erlang:fun_to_list(Fun),
+    LPid = maps:get(pid, PM),
+    pid = maps:get(LPid, PM),
+    LRef = maps:get(ref, PM),
+    ref = maps:get(LRef, PM),
+    LPort = maps:get(port, PM),
+    port = maps:get(LPort, PM),
+    LFun = maps:get(a_fun, PM),
+    a_fun = maps:get(LFun, PM),
+    ok.
 
 %%%---------------------------------------------------------------------
 %%% Functions to test
-- 
2.16.4

openSUSE Build Service is sponsored by