File 2174-erts-Escape-atoms-in-erlang-fun_to_list-1.patch of Package erlang

From 6a9db8b37b8f5a587ffc7622a097bf9c2f6af3e0 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Tue, 6 Aug 2019 15:52:16 +0200
Subject: [PATCH] erts: Escape atoms in erlang:fun_to_list/1

---
 erts/emulator/beam/erl_printf_term.c | 29 +++++++++++++++++++++++++----
 erts/emulator/test/fun_SUITE.erl     | 10 ++++++++--
 2 files changed, 33 insertions(+), 6 deletions(-)

diff --git a/erts/emulator/beam/erl_printf_term.c b/erts/emulator/beam/erl_printf_term.c
index 2e33a8a782..67c486a0db 100644
--- a/erts/emulator/beam/erl_printf_term.c
+++ b/erts/emulator/beam/erl_printf_term.c
@@ -533,13 +533,34 @@ print_term(fmtfn_t fn, void* arg, Eterm obj, long *dcount) {
 	case EXPORT_DEF:
 	    {
 		Export* ep = *((Export **) (export_val(wobj) + 1));
-		Atom* module = atom_tab(atom_val(ep->info.mfa.module));
-		Atom* name = atom_tab(atom_val(ep->info.mfa.function));
+		long tdcount;
+		int tres;
 
 		PRINT_STRING(res, fn, arg, "fun ");
-		PRINT_BUF(res, fn, arg, module->name, module->len);
+
+		/* We pass a temporary 'dcount' and adjust the real one later to ensure
+		 * that the fun doesn't get split up between the module and function
+		 * name. */
+		tdcount = MAX_ATOM_SZ_LIMIT;
+		tres = print_atom_name(fn, arg, ep->info.mfa.module, &tdcount);
+		if (tres < 0) {
+		    res = tres;
+		    goto L_done;
+		}
+		*dcount -= (MAX_ATOM_SZ_LIMIT - tdcount);
+		res += tres;
+
 		PRINT_CHAR(res, fn, arg, ':');
-		PRINT_BUF(res, fn, arg, name->name, name->len);
+
+		tdcount = MAX_ATOM_SZ_LIMIT;
+		tres = print_atom_name(fn, arg, ep->info.mfa.function, &tdcount);
+		if (tres < 0) {
+		    res = tres;
+		    goto L_done;
+		}
+		*dcount -= (MAX_ATOM_SZ_LIMIT - tdcount);
+		res += tres;
+
 		PRINT_CHAR(res, fn, arg, '/');
 		PRINT_SWORD(res, fn, arg, 'd', 0, 1,
 			    (ErlPfSWord) ep->info.mfa.arity);
diff --git a/erts/emulator/test/fun_SUITE.erl b/erts/emulator/test/fun_SUITE.erl
index 2cbde621ce..ad8ef0feff 100644
--- a/erts/emulator/test/fun_SUITE.erl
+++ b/erts/emulator/test/fun_SUITE.erl
@@ -27,7 +27,7 @@
 	 fun_to_port/1,t_phash/1,t_phash2/1,md5/1,
 	 refc/1,refc_ets/1,refc_dist/1,
 	 const_propagation/1,t_arity/1,t_is_function2/1,
-	 t_fun_info/1,t_fun_info_mfa/1]).
+	 t_fun_info/1,t_fun_info_mfa/1,t_fun_to_list/1]).
 
 -export([nothing/0]).
 
@@ -44,7 +44,7 @@ all() ->
      equality, ordering, fun_to_port, t_phash,
      t_phash2, md5, refc, refc_ets, refc_dist,
      const_propagation, t_arity, t_is_function2, t_fun_info,
-     t_fun_info_mfa].
+     t_fun_info_mfa,t_fun_to_list].
 
 %% Test that the correct EXIT code is returned for all types of bad funs.
 bad_apply(Config) when is_list(Config) ->
@@ -802,6 +802,12 @@ t_fun_info_mfa(Config) when is_list(Config) ->
     {'EXIT',_} = (catch erlang:fun_info_mfa(id(d))),
     ok.
 
+t_fun_to_list(Config) when is_list(Config) ->
+    "fun a:b/1" = erlang:fun_to_list(fun a:b/1),
+    "fun 'a-esc':'b-esc'/1" = erlang:fun_to_list(fun 'a-esc':'b-esc'/1),
+    "fun 'a-esc':b/1" = erlang:fun_to_list(fun 'a-esc':b/1),
+    "fun a:'b-esc'/1" = erlang:fun_to_list(fun a:'b-esc'/1),
+    ok.
 
 bad_info(Term) ->
     try	erlang:fun_info(Term, module) of
-- 
2.16.4

openSUSE Build Service is sponsored by