File 2310-Fail-early-when-calling_self.patch of Package erlang

From 8cd993c4a072711eff54c3d100dfa59b48cc95be Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Jos=C3=A9=20Valim?= <jose.valim@dashbit.co>
Date: Sun, 27 Jun 2021 17:21:40 +0200
Subject: [PATCH] Fail early when calling_self

This provides early feedback in gen behaviours if a process
attempts to call itself, which is especially important on
infinity timeouts.

The functionality was also implemented for the io module,
which also errors with reason "calling_self" and is handled
by the error formatter accordingly:

    1> io:put_chars(self(), "123").
    ** exception error: calling_self
         in function  io:put_chars/2
            called as io:put_chars(<0.83.0>,"123")
            *** argument 1: the device is not allowed to be the current process

Closes #5005.
---
 lib/stdlib/src/erl_error.erl         |  2 ++
 lib/stdlib/src/erl_stdlib_errors.erl |  7 +++++++
 lib/stdlib/src/gen.erl               |  2 ++
 lib/stdlib/src/io.erl                |  3 +++
 lib/stdlib/test/gen_server_SUITE.erl | 13 +++++++++++--
 lib/stdlib/test/io_SUITE.erl         | 10 ++++++++--
 6 files changed, 33 insertions(+), 4 deletions(-)

diff --git a/lib/stdlib/src/erl_error.erl b/lib/stdlib/src/erl_error.erl
index f6870b875b..4c4c3338f0 100644
--- a/lib/stdlib/src/erl_error.erl
+++ b/lib/stdlib/src/erl_error.erl
@@ -269,6 +269,8 @@ explain_reason(restricted_shell_started, exit, [], _PF, _S, _Enc, _CL) ->
     <<"restricted shell starts now">>;
 explain_reason(restricted_shell_stopped, exit, [], _PF, _S, _Enc, _CL) ->
     <<"restricted shell stopped">>;
+explain_reason(calling_self, exit, [], _PF, _S, _Enc, _CL) ->
+    <<"the current process attempted to call itself">>;
 %% Other exit code:
 explain_reason(Reason, Class, [], PF, S, _Enc, CL) ->
     {L, _} = PF(Reason, (iolist_size(S)+1) + exited_size(Class), CL),
diff --git a/lib/stdlib/src/erl_stdlib_errors.erl b/lib/stdlib/src/erl_stdlib_errors.erl
index a8c0744bc5..66f02a2b30 100644
--- a/lib/stdlib/src/erl_stdlib_errors.erl
+++ b/lib/stdlib/src/erl_stdlib_errors.erl
@@ -417,6 +417,11 @@ format_io_error(_, _, {io, arguments}, true) ->
     [device_arguments];
 format_io_error(_, _, {io, arguments}, false) ->
     [{general,device_arguments}];
+%% calling_self, Io =:= self()
+format_io_error(_, _, {io, calling_self}, true) ->
+    [calling_self];
+format_io_error(_, _, {io, calling_self}, false) ->
+    [{general,calling_self}];
 %% terminated, monitor(Io) failed
 format_io_error(_, _, {io, terminated}, true) ->
     [device_terminated];
@@ -988,6 +993,8 @@ expand_error(bad_update_op) ->
     <<"not a valid update operation">>;
 expand_error(bitstring) ->
     <<"is a bitstring (expected a binary)">>;
+expand_error(calling_self) ->
+    <<"the device is not allowed to be the current process">>;
 expand_error(counter_not_integer) ->
     <<"the value in the given position, in the object, is not an integer">>;
 expand_error(dead_process) ->
diff --git a/lib/stdlib/src/gen.erl b/lib/stdlib/src/gen.erl
index 6a07eb34d8..604815d15a 100644
--- a/lib/stdlib/src/gen.erl
+++ b/lib/stdlib/src/gen.erl
@@ -201,6 +201,8 @@ call(Process, Label, Request, Timeout)
 
 -dialyzer({no_improper_lists, do_call/4}).
 
+do_call(Process, _Label, _Request, _Timeout) when Process =:= self() ->
+    exit(calling_self);
 do_call(Process, Label, Request, infinity)
   when (is_pid(Process)
         andalso (node(Process) == node()))
diff --git a/lib/stdlib/src/io.erl b/lib/stdlib/src/io.erl
index d93be2d997..956f1ad013 100644
--- a/lib/stdlib/src/io.erl
+++ b/lib/stdlib/src/io.erl
@@ -335,6 +335,7 @@ read(Io, Prompt, Pos0, Options) ->
 
 conv_reason(arguments) -> badarg;
 conv_reason(terminated) -> terminated;
+conv_reason(calling_self) -> calling_self;
 conv_reason({no_translation,_,_}) -> no_translation;
 conv_reason(_Reason) -> badarg.
 
@@ -596,6 +597,8 @@ request(Name, Request, ErrorTag) when is_atom(Name) ->
 	    request(Pid, Request, ErrorTag)
     end.
 
+execute_request(Pid, _Tuple, ErrorTag) when Pid =:= self() ->
+    {ErrorTag, calling_self};
 execute_request(Pid, {Convert,Converted}, ErrorTag) ->
     Mref = erlang:monitor(process, Pid),
     Pid ! {io_request,self(),Mref,Converted},
diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl
index 0a7cf80923..1da9845731 100644
--- a/lib/stdlib/test/gen_server_SUITE.erl
+++ b/lib/stdlib/test/gen_server_SUITE.erl
@@ -28,7 +28,7 @@
 	 init_per_group/2,end_per_group/2]).
 -export([start/1, crash/1, call/1, send_request/1, cast/1, cast_fast/1,
 	 continue/1, info/1, abcast/1, multicall/1, multicall_down/1,
-	 call_remote1/1, call_remote2/1, call_remote3/1,
+	 call_remote1/1, call_remote2/1, call_remote3/1, calling_self/1,
 	 call_remote_n1/1, call_remote_n2/1, call_remote_n3/1, spec_init/1,
 	 spec_init_local_registered_parent/1, 
 	 spec_init_global_registered_parent/1,
@@ -65,7 +65,7 @@ suite() ->
 
 all() -> 
     [start, {group,stop}, crash, call, send_request, cast, cast_fast, info, abcast,
-     continue, multicall, multicall_down, call_remote1, call_remote2,
+     continue, multicall, multicall_down, call_remote1, call_remote2, calling_self,
      call_remote3, call_remote_n1, call_remote_n2,
      call_remote_n3, spec_init,
      spec_init_local_registered_parent,
@@ -720,6 +720,15 @@ call_remote_n3(Config) when is_list(Config) ->
 
     ok.
 
+%% --------------------------------------
+%% Other bad calls
+%% --------------------------------------
+
+calling_self(Config) when is_list(Config) ->
+    {'EXIT', {calling_self, _}} = (catch gen_server:call(self(), oops)),
+    {'EXIT', {calling_self, _}} = (catch gen_server:call(self(), oops, infinity)),
+    ok.
+
 %% --------------------------------------
 %% Test gen_server:cast and handle_cast.
 %% Test all different return values from
diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl
index 6cf9d9f7d6..9f36c694d0 100644
--- a/lib/stdlib/test/io_SUITE.erl
+++ b/lib/stdlib/test/io_SUITE.erl
@@ -28,7 +28,7 @@
 	 io_fread_newlines/1, otp_8989/1, io_lib_fread_literal/1,
 	 printable_range/1, bad_printable_range/1,
 	 io_lib_print_binary_depth_one/1, otp_10302/1, otp_10755/1,
-         otp_10836/1, io_lib_width_too_small/1,
+         otp_10836/1, io_lib_width_too_small/1, calling_self/1,
          io_with_huge_message_queue/1, format_string/1, format_neg_zero/1,
 	 maps/1, coverage/1, otp_14178_unicode_atoms/1, otp_14175/1,
          otp_14285/1, limit_term/1, otp_14983/1, otp_15103/1, otp_15076/1,
@@ -63,7 +63,7 @@ all() ->
      io_fread_newlines, otp_8989, io_lib_fread_literal,
      printable_range, bad_printable_range, format_neg_zero,
      io_lib_print_binary_depth_one, otp_10302, otp_10755, otp_10836,
-     io_lib_width_too_small, io_with_huge_message_queue,
+     io_lib_width_too_small, io_with_huge_message_queue, calling_self,
      format_string, maps, coverage, otp_14178_unicode_atoms, otp_14175,
      otp_14285, limit_term, otp_14983, otp_15103, otp_15076, otp_15159,
      otp_15639, otp_15705, otp_15847, otp_15875, github_4801, chars_limit,
@@ -210,6 +210,10 @@ float_w(Config) when is_list(Config) ->
 
     ok.
 
+calling_self(Config) when is_list(Config) ->
+    {'EXIT', {calling_self, _}} = (catch io:format(self(), "~p", [oops])),
+    ok.
+
 %% OTP-5403. ~s formats I/O lists and a single binary.
 otp_5403(Config) when is_list(Config) ->
     "atom" = fmt("~s", [atom]),
@@ -3034,6 +3038,8 @@ error_info(Config) ->
          {put_chars,[<<1:1>>], [{1,"not valid character data"}]},
          {put_chars,[UnknownDev(),"test"], [{general,"unknown error: 'Спутник-1'"}]},
          {put_chars,["test"], [{gl,UnknownDev()},{general,"unknown error: 'Спутник-1'"}]},
+         {put_chars,[self(),"test"],[{1,"the device is not allowed to be the current process"}]},
+         {put_chars,["test"],[{gl,self()},{general,"the device is not allowed to be the current process"}]},
 
          {write,[DeadDev,"test"],[{1,"terminated"}]},
          {write,["test"],[{gl,DeadDev},{general,"terminated"}]},
-- 
2.31.1

openSUSE Build Service is sponsored by