diff --git a/lib/stdlib/src/gen.erl b/lib/stdlib/src/gen.erl index 2da31bb870f1..23f8dbdb35cb 100644 --- a/lib/stdlib/src/gen.erl +++ b/lib/stdlib/src/gen.erl @@ -178,7 +178,7 @@ monitor_return({Error, Mon}) when is_reference(Mon) -> %% Failure; wait for spawned process to terminate %% and release resources, then return the error... receive - {'DOWN', Mon, process, _Pid, _Reason} -> + {_Tag, Mon, process, _Pid, _Reason} -> ok end, Error. diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl index 041db1ee1d57..53668897297e 100644 --- a/lib/stdlib/src/proc_lib.erl +++ b/lib/stdlib/src/proc_lib.erl @@ -98,15 +98,17 @@ processes that terminate as a result of this process terminating. %% -doc """ A restricted set of [spawn options](`t:spawn_option/0`). Most notably `monitor` -is _not_ part of these options. +and `{monitor, MonitorOpts}` are _not_ part of these options. """. -type start_spawn_option() :: 'link' + | {'link', [erlang:link_option()]} | {'priority', erlang:priority_level()} | {'fullsweep_after', non_neg_integer()} | {'min_heap_size', non_neg_integer()} | {'min_bin_vheap_size', non_neg_integer()} | {'max_heap_size', erlang:max_heap_size()} - | {'message_queue_data', erlang:message_queue_data() }. + | {'message_queue_data', erlang:message_queue_data()} + | {'async_dist', boolean()}. %% and this macro is used to verify that there are no monitor options %% which also needs to be kept in sync all kinds of monitor options %% in erlang:spawn_opt_options(). @@ -417,11 +419,11 @@ Argument `SpawnOpts`, if specified, is passed as the last argument to the > #### Note {: .info } > -> Using spawn option `monitor` is not allowed. It causes the function to fail -> with reason `badarg`. +> Using spawn option `monitor` or `{monitor, Opts}` is not allowed. It causes +> the function to fail with reason `badarg`. > -> Using spawn option `link` will set a link to the spawned process, just like -> [start_link/3,4,5](`start_link/3`). +> Using spawn option `link` or `{link, Opts}` will set a link to the spawned +> process, just like [start_link/3,4,5](`start_link/3`). """. -spec start(Module, Function, Args, Time, SpawnOpts) -> Ret when Module :: module(), @@ -497,8 +499,11 @@ process. > #### Note {: .info } > -> Using spawn option `monitor` is not allowed. It causes the function to fail -> with reason `badarg`. +> Using spawn option `monitor` or `{monitor, Opts}` is not allowed. It causes +> the function to fail with reason `badarg`. +> +> Using spawn option `link` has no effect. The spawn option `{link, Opts}` can +> be used to customize the link that will be set to the spawned process. """. -spec start_link(Module, Function, Args, Time, SpawnOpts) -> Ret when Module :: module(), @@ -510,8 +515,9 @@ process. start_link(M,F,A,Timeout,SpawnOpts) when is_atom(M), is_atom(F), is_list(A) -> ?VERIFY_NO_MONITOR_OPT(M, F, A, Timeout, SpawnOpts), + SpawnOpts1 = ensure_spawn_option(link, SpawnOpts), sync_start( - ?MODULE:spawn_opt(M, F, A, [link,monitor|SpawnOpts]), Timeout). + ?MODULE:spawn_opt(M, F, A, [monitor | SpawnOpts1]), Timeout). -doc(#{equiv => start_monitor(Module, Function, Args, infinity)}). @@ -556,11 +562,11 @@ when this function times out and kills the spawned process. > #### Note {: .info } > -> Using spawn option `monitor` is not allowed. It causes the function to fail -> with reason `badarg`. +> Using spawn option `monitor` has no effect. The spawn option `{monitor, Opts}` +> can be used to customize the monitor that will be set on the spawned process. > -> Using spawn option `link` will set a link to the spawned process, just like -> [start_link/3,4,5](`start_link/3`). +> Using spawn option `link` or `{link, Opts}` will set a link to the spawned +> process, just like [start_link/3,4,5](`start_link/3`). """. -doc(#{since => <<"OTP 23.0">>}). -spec start_monitor(Module, Function, Args, Time, SpawnOpts) -> {Ret, Mon} when @@ -568,16 +574,16 @@ when this function times out and kills the spawned process. Function :: atom(), Args :: [term()], Time :: timeout(), - SpawnOpts :: [start_spawn_option()], + SpawnOpts :: [spawn_option()], Mon :: reference(), Ret :: term() | {error, Reason :: term()}. start_monitor(M,F,A,Timeout,SpawnOpts) when is_atom(M), is_atom(F), is_list(A) -> - ?VERIFY_NO_MONITOR_OPT(M, F, A, Timeout, SpawnOpts), + SpawnOpts1 = ensure_spawn_option(monitor, SpawnOpts), sync_start_monitor( - ?MODULE:spawn_opt(M, F, A, [monitor|SpawnOpts]), Timeout). + ?MODULE:spawn_opt(M, F, A, SpawnOpts1), Timeout). sync_start_monitor({Pid, Ref}, Timeout) -> receive @@ -587,7 +593,7 @@ sync_start_monitor({Pid, Ref}, Timeout) -> flush_EXIT(Pid), self() ! await_DOWN(Pid, Ref), {Return, Ref}; - {'DOWN', Ref, process, Pid, Reason} = Down -> + {_, Ref, process, Pid, Reason} = Down -> flush_EXIT(Pid), self() ! Down, {{error, Reason}, Ref} @@ -597,6 +603,19 @@ sync_start_monitor({Pid, Ref}, Timeout) -> {{error, timeout}, Ref} end. +%% Adds the given Opt atom to the given SpawnOpts list +%% if it is not already contained either in plain form +%% or as the first element of a tuple. +ensure_spawn_option(Opt, [Opt | _] = SpawnOpts) -> + SpawnOpts; +ensure_spawn_option(Opt, [SpawnOpt | _] = SpawnOpts) + when Opt =:= element(1, SpawnOpt) -> + SpawnOpts; +ensure_spawn_option(Opt, [SpawnOpt | SpawnOpts]) -> + [SpawnOpt | ensure_spawn_option(Opt, SpawnOpts)]; +ensure_spawn_option(Opt, []) -> + [Opt]. + %% We regard the existence of an {'EXIT', Pid, _} message %% as proof enough that there was a link that fired and @@ -620,7 +639,7 @@ kill_flush_EXIT(Pid) -> await_DOWN(Pid, Ref) -> receive - {'DOWN', Ref, process, Pid, _} = Down -> + {_, Ref, process, Pid, _} = Down -> Down end. diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl index 2818b5be6b86..ff2790db3ba8 100644 --- a/lib/stdlib/test/proc_lib_SUITE.erl +++ b/lib/stdlib/test/proc_lib_SUITE.erl @@ -29,11 +29,11 @@ -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2, crash/1, stacktrace/1, sync_start_nolink/1, sync_start_link/1, - sync_start_monitor/1, sync_start_monitor_link/1, + sync_start_monitor/1, sync_start_monitor_link/1, sync_start_monitor_monitor/1, sync_start_timeout/1, sync_start_link_timeout/1, sync_start_monitor_link_timeout/1, spawn_opt/1, sp1/0, sp1_with_label/0, sp2/0, sp3/1, sp4/2, - sp5/1, sp6/1, sp7/1, sp8/1, sp9/1, sp10/1, + sp5/1, sp6/1, sp7_link/1, sp7_monitor/1, sp8/1, sp9/1, sp10/1, '\x{447}'/0, hibernate/1, stop/1, t_format/1, t_format_arbitrary/1]). -export([ otp_6345/1, init_dont_hang/1]). @@ -64,7 +64,7 @@ all() -> groups() -> [{tickets, [], [otp_6345, init_dont_hang]}, {sync_start, [], [sync_start_nolink, sync_start_link, - sync_start_monitor, sync_start_monitor_link, + sync_start_monitor, sync_start_monitor_link, sync_start_monitor_monitor, sync_start_timeout, sync_start_link_timeout, sync_start_monitor_link_timeout]}]. @@ -313,7 +313,7 @@ sync_start_monitor(Config) when is_list(Config) -> ok. sync_start_monitor_link(Config) when is_list(Config) -> - _Pid = spawn_link(?MODULE, sp7, [self()]), + _Pid = spawn_link(?MODULE, sp7_link, [self()]), receive {sync_started, _} -> ct:fail(async_start) after 1000 -> ok @@ -334,6 +334,26 @@ sync_start_monitor_link(Config) when is_list(Config) -> end, ok. +sync_start_monitor_monitor(Config) when is_list(Config) -> + _Pid = spawn_link(?MODULE, sp7_monitor, [self()]), + receive + {sync_started, _} -> ct:fail(async_start) + after 1000 -> ok + end, + receive + {Pid2, init} -> + Pid2 ! go_on + end, + receive + {sync_started, _} -> ok + after 1000 -> ct:fail(no_sync_start) + end, + receive received_down -> ok + after 1000 -> ct:fail(no_down) + end, + ok. + + sync_start_timeout(Config) when is_list(Config) -> _Pid = spawn_link(?MODULE, sp8, [self()]), receive done -> ok end, @@ -445,7 +465,7 @@ sp6(Tester) -> Tester ! received_down end. -sp7(Tester) -> +sp7_link(Tester) -> process_flag(trap_exit, true), {Pid, Mon} = proc_lib:start_monitor(?MODULE, sp4, [self(), Tester], infinity, [link]), Tester ! {sync_started, Pid}, @@ -458,6 +478,15 @@ sp7(Tester) -> Tester ! received_down end. +sp7_monitor(Tester) -> + process_flag(trap_exit, true), + {Pid, Mon} = proc_lib:start_monitor(?MODULE, sp4, [self(), Tester], infinity, [{monitor, [{tag, sp7_monitor}]}]), + Tester ! {sync_started, Pid}, + receive + {sp7_monitor, Mon, process, Pid, normal} -> + Tester ! received_down + end. + sp8(Tester) -> process_flag(trap_exit, true), {error,timeout} = proc_lib:start(?MODULE, sp4, [self(), Tester], 500, [link]), @@ -622,8 +651,12 @@ hib_receive_messages(N) -> otp_6345(Config) when is_list(Config) -> Opts = [link,monitor], try - blupp = proc_lib:start(?MODULE, otp_6345_init, [self()], - 1000, Opts) + proc_lib:start(?MODULE, otp_6345_init, [self()], + 1000, Opts) + of + {ok, Pid} -> + exit(Pid, kill), + ct:fail(monitor_option_accepted) catch error:badarg -> ok end.