File 2951-ssh-Make-ssh_dbg-a-behaviour.patch of Package erlang

From 83171f4af9b8eef64714d14ddb3fa6f8f4f4153c Mon Sep 17 00:00:00 2001
From: Hans Nilsson <hans@erlang.org>
Date: Wed, 4 Dec 2019 17:30:42 +0100
Subject: [PATCH 1/2] ssh: Make ssh_dbg a behaviour

---
 lib/ssh/src/Makefile    | 19 ++++++++---
 lib/ssh/src/ssh_dbg.erl | 85 ++++++++++++++++++++++++++++---------------------
 2 files changed, 63 insertions(+), 41 deletions(-)

diff --git a/lib/ssh/src/Makefile b/lib/ssh/src/Makefile
index 9627b70eeb..f5c520f2f0 100644
--- a/lib/ssh/src/Makefile
+++ b/lib/ssh/src/Makefile
@@ -39,7 +39,13 @@ RELSYSDIR = $(RELEASE_PATH)/lib/ssh-$(VSN)
 
 # Behaviour (api) modules are first so they are compiled when
 # the compiler reaches a callback module using them.
-BEHAVIOUR_MODULES= \
+# The $(BEHAVIOUR_MODULES_1) has a behaviour used in one or more
+# of the $(BEHAVIOUR_MODULES_2)
+
+BEHAVIOUR_MODULES_1= \
+	ssh_dbg
+
+BEHAVIOUR_MODULES_2= \
 	ssh_client_key_api \
 	ssh_daemon_channel \
 	ssh_server_channel \
@@ -59,7 +65,6 @@ MODULES= \
 	ssh_connection \
 	ssh_connection_handler \
 	ssh_connection_sup \
-	ssh_dbg \
 	ssh_file \
 	ssh_info \
 	ssh_io \
@@ -83,12 +88,15 @@ HRL_FILES =
 
 ERL_FILES= \
 	$(MODULES:%=%.erl) \
-	$(BEHAVIOUR_MODULES:%=%.erl)
+	$(BEHAVIOUR_MODULES_1:%=%.erl) \
+	$(BEHAVIOUR_MODULES_2:%=%.erl)
 
 
 TARGET_FILES= $(MODULES:%=$(EBIN)/%.$(EMULATOR))
 
-BEHAVIOUR_TARGET_FILES= $(BEHAVIOUR_MODULES:%=$(EBIN)/%.$(EMULATOR))
+BEHAVIOUR_TARGET_FILES_1= $(BEHAVIOUR_MODULES_1:%=$(EBIN)/%.$(EMULATOR))
+BEHAVIOUR_TARGET_FILES_2= $(BEHAVIOUR_MODULES_2:%=$(EBIN)/%.$(EMULATOR))
+BEHAVIOUR_TARGET_FILES= $(BEHAVIOUR_TARGET_FILES_1) $(BEHAVIOUR_TARGET_FILES_2)
 
 APP_FILE= ssh.app
 APPUP_FILE= ssh.appup
@@ -115,7 +123,8 @@ ERL_COMPILE_FLAGS += -I$(ERL_TOP)/lib/kernel/src \
 # Targets
 # ----------------------------------------------------
 
-$(TARGET_FILES): $(BEHAVIOUR_TARGET_FILES)
+$(TARGET_FILES): $(BEHAVIOUR_TARGET_FILES_2)
+$(BEHAVIOUR_TARGET_FILES_2): $(BEHAVIOUR_TARGET_FILES_1)
 
 debug opt: $(TARGET_FILES) $(APP_TARGET) $(APPUP_TARGET)
 
diff --git a/lib/ssh/src/ssh_dbg.erl b/lib/ssh/src/ssh_dbg.erl
index 43ac4c0ccf..7b7f9909ac 100644
--- a/lib/ssh/src/ssh_dbg.erl
+++ b/lib/ssh/src/ssh_dbg.erl
@@ -80,6 +80,15 @@
 
 -define(CALL_TIMEOUT, 15000). % 3x the default
 
+-type trace_point() :: atom().
+-type trace_points() :: [trace_point()].
+
+-callback ssh_dbg_trace_points() -> trace_points().
+-callback ssh_dbg_flags(trace_point()) -> [atom()].
+-callback ssh_dbg_on(trace_point() | trace_points()) -> term().
+-callback ssh_dbg_off(trace_point() | trace_points()) -> term().
+-callback ssh_dbg_format(trace_point(), term()) -> iolist().
+
 %%%================================================================
 
 -define(ALL_DBG_TYPES, get_all_dbg_types()).
@@ -170,13 +179,13 @@ init(_) ->
 %%%----------------------------------------------------------------
 handle_call({switch,on,Types}, _From, D) ->
     NowOn = lists:usort(Types ++ D#data.types_on),
-    call_modules(on, Types, NowOn),
+    call_modules(on, Types),
     {reply, {ok,NowOn}, D#data{types_on = NowOn}};
 
 handle_call({switch,off,Types}, _From, D) ->
     StillOn = D#data.types_on -- Types,
-    call_modules(off, Types, StillOn),
-    call_modules(on, StillOn, StillOn),
+    call_modules(off, Types),
+    call_modules(on, StillOn),
     {reply, {ok,StillOn}, D#data{types_on = StillOn}};
 
 handle_call(get_on, _From, D) ->
@@ -202,52 +211,54 @@ handle_info(C, D) ->
 ssh_modules_with_trace() ->
     {ok,AllSshModules} = application:get_key(ssh, modules),
     [M || M <- AllSshModules,
-          lists:member({dbg_trace,3}, M:module_info(exports))].
+          {behaviour,Bs} <- M:module_info(attributes),
+          lists:member(?MODULE, Bs)
+    ].
 
 %%%----------------------------------------------------------------
 get_all_trace_flags() ->
-    get_all_trace_flags(ssh_modules_with_trace()).
-
-get_all_trace_flags(Modules) ->
     lists:usort(
-      lists:flatten(
-        lists:foldl(
-          fun(Type, Acc) ->
-                  call_modules(flags, Type, undefined, Acc, Modules)
-          end, [timestamp], ?ALL_DBG_TYPES))).
+      lists:flatten([timestamp |  call_modules(flags, ?ALL_DBG_TYPES)]
+                   )).
 
 %%%----------------------------------------------------------------
 get_all_dbg_types() ->
     lists:usort(
       lists:flatten(
-        call_modules(points, undefined) )).
+        call_modules(points) )).
 
 %%%----------------------------------------------------------------
-call_modules(Cmnd, Type) ->
-    call_modules(Cmnd, Type, undefined).
-
-call_modules(Cmnd, Type, Arg) ->
-    call_modules(Cmnd, Type, Arg, []).
+call_modules(points) ->
+    F = fun(Mod) -> Mod:ssh_dbg_trace_points() end,
+    fold_modules(F, [], ssh_modules_with_trace()).
+
+call_modules(Cmnd, Types) when is_list(Types) ->
+    F = case Cmnd of
+            flags -> fun(Type) ->
+                             fun(Mod) -> Mod:ssh_dbg_flags(Type) end
+                     end;
+            on -> fun(Type) ->
+                          fun(Mod) -> Mod:ssh_dbg_on(Type) end
+                  end;
+            off -> fun(Type) ->
+                           fun(Mod) -> Mod:ssh_dbg_off(Type) end
+                   end
+        end,
+    lists:foldl(fun(T, Acc) ->
+                        fold_modules(F(T), Acc, ssh_modules_with_trace())
+                end, [], Types).
 
-call_modules(Cmnd, Type, Arg, Acc0) ->
-    call_modules(Cmnd, Type, Arg, Acc0, ssh_modules_with_trace()).
 
-call_modules(Cmnd, Types, Arg, Acc0, Modules) when is_list(Types) ->
-    lists:foldl(
-       fun(Type, Acc) ->
-               call_modules(Cmnd, Type, Arg, Acc, Modules)
-       end, Acc0, Types);
 
-call_modules(Cmnd, Type, Arg, Acc0, Modules) ->
-    lists:foldl(
-      fun(Mod, Acc) ->
-              try Mod:dbg_trace(Cmnd, Type, Arg)
-              of
-                  Result -> [Result|Acc]
-              catch
-                  _:_ -> Acc
-              end
-      end, Acc0, Modules).
+fold_modules(F, Acc0, Modules) ->
+     lists:foldl(
+       fun(Mod, Acc) ->
+               try F(Mod) of
+                   Result -> [Result|Acc]
+               catch
+                   _:_ -> Acc
+               end
+       end, Acc0, Modules).
 
 %%%----------------------------------------------------------------
 switch(X, Type) when is_atom(Type) ->
@@ -314,7 +325,9 @@ try_all_types_in_all_modules(TypesOn, Arg, WriteFun, Acc0) ->
               lists:foldl(
                 fun(SshMod,Acc) ->
                         try WriteFun("~n~s ~p ~s~n", 
-                                     [lists:flatten(TS), PID, lists:flatten(SshMod:dbg_trace(format,Type,INFO))],
+                                     [lists:flatten(TS),
+                                      PID,
+                                      lists:flatten(SshMod:ssh_dbg_format(Type, INFO))],
                                      Acc)
                         catch
                             _:_ -> Acc
-- 
2.16.4

openSUSE Build Service is sponsored by