File 0340-stdlib-sys-install-one-debug-function-more-times-178.patch of Package erlang

From eefcc985530acbd5cc4c97b6e4f537492fd61622 Mon Sep 17 00:00:00 2001
From: Pouriya <pouriya.jahanbakhsh@gmail.com>
Date: Thu, 26 Apr 2018 13:49:59 +0000
Subject: [PATCH] [stdlib/sys]: install one debug function more times (#1781)

Allow installing multiple instances of sys debug function

This commit solves a bug which allowed installing {Fun,State} as sys debug function even if Fun was already installed. This happened in the case when the current State of the debug fun was undefined.

Also, the new format {Id,Fun,State} of debug functions can be installed, allowing multiple instances of the same fun.
---
 lib/stdlib/doc/src/sys.xml    |  8 +++---
 lib/stdlib/src/sys.erl        | 57 +++++++++++++++++++++++++++++--------------
 lib/stdlib/test/sys_SUITE.erl | 24 +++++++++++++++---
 3 files changed, 65 insertions(+), 24 deletions(-)

diff --git a/lib/stdlib/doc/src/sys.xml b/lib/stdlib/doc/src/sys.xml
index 8930087555..59e5bb6cb5 100644
--- a/lib/stdlib/doc/src/sys.xml
+++ b/lib/stdlib/doc/src/sys.xml
@@ -276,7 +276,9 @@
         <p><c><anno>Func</anno></c> is called whenever a system event is
           generated. This function is to return <c>done</c>, or a new
           <c>Func</c> state. In the first case, the function is removed. It is 
-          also removed if the function fails.</p>
+          also removed if the function fails. If one debug function should be 
+          installed more times, a unique <c><anno>FuncId</anno></c> must be 
+          specified for each installation.</p>
       </desc>
     </func>
 
@@ -330,8 +332,8 @@
       <fsummary>Remove a debug function from the process.</fsummary>
       <desc>
         <p>Removes an installed debug function from the
-          process. <c><anno>Func</anno></c> must be the same as previously
-          installed.</p>
+          process. <c><anno>Func</anno></c> or <c><anno>FuncId</anno></c> must be 
+          the same as previously installed.</p>
       </desc>
     </func>
 
diff --git a/lib/stdlib/src/sys.erl b/lib/stdlib/src/sys.erl
index b1177ece48..0064414d6f 100644
--- a/lib/stdlib/src/sys.erl
+++ b/lib/stdlib/src/sys.erl
@@ -57,7 +57,8 @@
                                         MessagesIn :: non_neg_integer(),
                                         MessagesOut :: non_neg_integer()}}
                       | {'log_to_file', file:io_device()}
-                      | {Func :: dbg_fun(), FuncState :: term()}.
+                      | {Func :: dbg_fun(), FuncState :: term()}
+                      | {FuncId :: term(), Func :: dbg_fun(), FuncState :: term()}.
 -type dbg_fun()      :: fun((FuncState :: _,
                              Event :: system_event(),
                              ProcState :: _) -> 'done' | (NewFuncState :: _)).
@@ -268,33 +269,41 @@ no_debug(Name, Timeout) -> send_system_msg(Name, {debug, no_debug}, Timeout).
 
 -spec install(Name, FuncSpec) -> 'ok' when
       Name :: name(),
-      FuncSpec :: {Func, FuncState},
+      FuncSpec :: {Func, FuncState} | {FuncId, Func, FuncState},
+      FuncId :: term(),
       Func :: dbg_fun(),
       FuncState :: term().
 install(Name, {Func, FuncState}) ->
-    send_system_msg(Name, {debug, {install, {Func, FuncState}}}).
+    send_system_msg(Name, {debug, {install, {Func, FuncState}}});
+install(Name, {FuncId, Func, FuncState}) ->
+    send_system_msg(Name, {debug, {install, {FuncId, Func, FuncState}}}).
 
 -spec install(Name, FuncSpec, Timeout) -> 'ok' when
       Name :: name(),
-      FuncSpec :: {Func, FuncState},
+      FuncSpec :: {Func, FuncState} | {FuncId, Func, FuncState},
+      FuncId :: term(),
       Func :: dbg_fun(),
       FuncState :: term(),
       Timeout :: timeout().
 install(Name, {Func, FuncState}, Timeout) ->
-    send_system_msg(Name, {debug, {install, {Func, FuncState}}}, Timeout).
+    send_system_msg(Name, {debug, {install, {Func, FuncState}}}, Timeout);
+install(Name, {FuncId, Func, FuncState}, Timeout) ->
+    send_system_msg(Name, {debug, {install, {FuncId, Func, FuncState}}}, Timeout).
 
--spec remove(Name, Func) -> 'ok' when
+-spec remove(Name, Func | FuncId) -> 'ok' when
       Name :: name(),
-      Func :: dbg_fun().
-remove(Name, Func) ->
-    send_system_msg(Name, {debug, {remove, Func}}).
+      Func :: dbg_fun(),
+      FuncId :: term().
+remove(Name, FuncOrFuncId) ->
+    send_system_msg(Name, {debug, {remove, FuncOrFuncId}}).
 
--spec remove(Name, Func, Timeout) -> 'ok' when
+-spec remove(Name, Func | FuncId, Timeout) -> 'ok' when
       Name :: name(),
       Func :: dbg_fun(),
+      FuncId :: term(),
       Timeout :: timeout().
-remove(Name, Func, Timeout) ->
-    send_system_msg(Name, {debug, {remove, Func}}, Timeout).
+remove(Name, FuncOrFuncId, Timeout) ->
+    send_system_msg(Name, {debug, {remove, FuncOrFuncId}}, Timeout).
 
 %%-----------------------------------------------------------------
 %% All system messages sent are on the form {system, From, Msg}
@@ -388,6 +397,13 @@ handle_debug([{log_to_file, Fd} | T], FormFunc, State, Event) ->
 handle_debug([{statistics, StatData} | T], FormFunc, State, Event) ->
     NStatData = stat(Event, StatData),
     [{statistics, NStatData} | handle_debug(T, FormFunc, State, Event)];
+handle_debug([{FuncId, {Func, FuncState}} | T], FormFunc, State, Event) ->
+    case catch Func(FuncState, Event, State) of
+        done -> handle_debug(T, FormFunc, State, Event);
+        {'EXIT', _} -> handle_debug(T, FormFunc, State, Event);
+        NFuncState ->
+            [{FuncId, {Func, NFuncState}} | handle_debug(T, FormFunc, State, Event)]
+    end;
 handle_debug([{Func, FuncState} | T], FormFunc, State, Event) ->
     case catch Func(FuncState, Event, State) of
 	done -> handle_debug(T, FormFunc, State, Event);
@@ -545,8 +561,10 @@ debug_cmd(no_debug, Debug) ->
     {ok, []};
 debug_cmd({install, {Func, FuncState}}, Debug) ->
     {ok, install_debug(Func, FuncState, Debug)};
-debug_cmd({remove, Func}, Debug) ->
-    {ok, remove_debug(Func, Debug)};
+debug_cmd({install, {FuncId, Func, FuncState}}, Debug) ->
+    {ok, install_debug(FuncId, {Func, FuncState}, Debug)};
+debug_cmd({remove, FuncOrFuncId}, Debug) ->
+    {ok, remove_debug(FuncOrFuncId, Debug)};
 debug_cmd(_Unknown, Debug) ->
     {unknown_debug, Debug}.
 
@@ -584,9 +602,9 @@ trim(N, LogData) ->
 %% Debug structure manipulating functions
 %%-----------------------------------------------------------------
 install_debug(Item, Data, Debug) ->
-    case get_debug2(Item, Debug, undefined) of
-	undefined -> [{Item, Data} | Debug];
-	_ -> Debug
+    case lists:keysearch(Item, 1, Debug) of
+        false -> [{Item, Data} | Debug];
+        _ -> Debug
     end.
 remove_debug(Item, Debug) -> lists:keydelete(Item, 1, Debug).
 
@@ -637,7 +655,8 @@ close_log_file(Debug) ->
            | {'log_to_file', FileName}
            | {'install', FuncSpec},
       FileName :: file:name(),
-      FuncSpec :: {Func, FuncState},
+      FuncSpec :: {Func, FuncState} | {FuncId, Func, FuncState},
+      FuncId :: term(),
       Func :: dbg_fun(),
       FuncState :: term().
 debug_options(Options) ->
@@ -660,6 +679,8 @@ debug_options([{log_to_file, FileName} | T], Debug) ->
     end;
 debug_options([{install, {Func, FuncState}} | T], Debug) ->
     debug_options(T, install_debug(Func, FuncState, Debug));
+debug_options([{install, {FuncId, Func, FuncState}} | T], Debug) ->
+    debug_options(T, install_debug(FuncId, {Func, FuncState}, Debug));
 debug_options([_ | T], Debug) ->
     debug_options(T, Debug);
 debug_options([], Debug) -> 
diff --git a/lib/stdlib/test/sys_SUITE.erl b/lib/stdlib/test/sys_SUITE.erl
index a28eca513f..439a23d82d 100644
--- a/lib/stdlib/test/sys_SUITE.erl
+++ b/lib/stdlib/test/sys_SUITE.erl
@@ -133,7 +133,8 @@ install(Config) when is_list(Config) ->
 			Master ! {spy_got,{request,Arg},ProcState};
 		    Other ->
 			io:format("Trigged other=~p\n",[Other])
-		end
+		end,
+                func_state
 	end,
     sys:install(?server,{SpyFun,func_state}),
     {ok,-1} = (catch public_call(1)),
@@ -142,10 +143,27 @@ install(Config) when is_list(Config) ->
     sys:install(?server,{SpyFun,func_state}),
     sys:install(?server,{SpyFun,func_state}),
     {ok,-3} = (catch public_call(3)),
-    sys:remove(?server,SpyFun),
     {ok,-4} = (catch public_call(4)),
+    sys:remove(?server,SpyFun),
+    {ok,-5} = (catch public_call(5)),
+    [{spy_got,{request,1},sys_SUITE_server},
+     {spy_got,{request,3},sys_SUITE_server},
+     {spy_got,{request,4},sys_SUITE_server}] = get_messages(),
+
+    sys:install(?server,{id1, SpyFun, func_state}),
+    sys:install(?server,{id1, SpyFun, func_state}), %% should not be installed
+    sys:install(?server,{id2, SpyFun, func_state}),    
+    {ok,-1} = (catch public_call(1)),
+    %% We have two SpyFun installed:
     [{spy_got,{request,1},sys_SUITE_server},
-     {spy_got,{request,3},sys_SUITE_server}] = get_messages(),
+     {spy_got,{request,1},sys_SUITE_server}] = get_messages(),
+    sys:remove(?server, id1),
+    {ok,-1} = (catch public_call(1)),
+    %% We have one SpyFun installed:
+    [{spy_got,{request,1},sys_SUITE_server}] = get_messages(),
+    sys:no_debug(?server),
+    {ok,-1} = (catch public_call(1)),
+    [] = get_messages(),
     stop(),
     ok.
 
-- 
2.16.3

openSUSE Build Service is sponsored by