@@ -98,15 +98,17 @@ processes that terminate as a result of this process terminating.
9898% %
9999-doc """
100100A restricted set of [spawn options](`t:spawn_option/0`). Most notably `monitor`
101- is _not_ part of these options.
101+ and `{monitor, MonitorOpts}` are _not_ part of these options.
102102""" .
103103-type start_spawn_option () :: 'link'
104+ | {'link' , [erlang :link_option ()]}
104105 | {'priority' , erlang :priority_level ()}
105106 | {'fullsweep_after' , non_neg_integer ()}
106107 | {'min_heap_size' , non_neg_integer ()}
107108 | {'min_bin_vheap_size' , non_neg_integer ()}
108109 | {'max_heap_size' , erlang :max_heap_size ()}
109- | {'message_queue_data' , erlang :message_queue_data () }.
110+ | {'message_queue_data' , erlang :message_queue_data ()}
111+ | {'async_dist' , boolean ()}.
110112% % and this macro is used to verify that there are no monitor options
111113% % which also needs to be kept in sync all kinds of monitor options
112114% % in erlang:spawn_opt_options().
@@ -417,11 +419,11 @@ Argument `SpawnOpts`, if specified, is passed as the last argument to the
417419
418420> #### Note {: .info }
419421>
420- > Using spawn option `monitor` is not allowed. It causes the function to fail
421- > with reason `badarg`.
422+ > Using spawn option `monitor` or `{monitor, Opts}` is not allowed. It causes
423+ > the function to fail with reason `badarg`.
422424>
423- > Using spawn option `link` will set a link to the spawned process, just like
424- > [start_link/3,4,5](`start_link/3`).
425+ > Using spawn option `link` or `{link, Opts}` will set a link to the spawned
426+ > process, just like [start_link/3,4,5](`start_link/3`).
425427""" .
426428-spec start (Module , Function , Args , Time , SpawnOpts ) -> Ret when
427429 Module :: module (),
@@ -497,8 +499,11 @@ process.
497499
498500> #### Note {: .info }
499501>
500- > Using spawn option `monitor` is not allowed. It causes the function to fail
501- > with reason `badarg`.
502+ > Using spawn option `monitor` or `{monitor, Opts}` is not allowed. It causes
503+ > the function to fail with reason `badarg`.
504+ >
505+ > Using spawn option `link` has no effect. The spawn option `{link, Opts}` can
506+ > be used to customize the link that will be set to the spawned process.
502507""" .
503508-spec start_link (Module , Function , Args , Time , SpawnOpts ) -> Ret when
504509 Module :: module (),
@@ -510,8 +515,9 @@ process.
510515
511516start_link (M ,F ,A ,Timeout ,SpawnOpts ) when is_atom (M ), is_atom (F ), is_list (A ) ->
512517 ? VERIFY_NO_MONITOR_OPT (M , F , A , Timeout , SpawnOpts ),
518+ SpawnOpts1 = ensure_spawn_option (link , SpawnOpts ),
513519 sync_start (
514- ? MODULE :spawn_opt (M , F , A , [link , monitor | SpawnOpts ]), Timeout ).
520+ ? MODULE :spawn_opt (M , F , A , [monitor | SpawnOpts1 ]), Timeout ).
515521
516522
517523-doc (#{equiv => start_monitor (Module , Function , Args , infinity )}).
@@ -556,28 +562,28 @@ when this function times out and kills the spawned process.
556562
557563> #### Note {: .info }
558564>
559- > Using spawn option `monitor` is not allowed. It causes the function to fail
560- > with reason `badarg`.
565+ > Using spawn option `monitor` has no effect. The spawn option `{monitor, Opts}`
566+ > can be used to customize the monitor that will be set on the spawned process.
561567>
562- > Using spawn option `link` will set a link to the spawned process, just like
563- > [start_link/3,4,5](`start_link/3`).
568+ > Using spawn option `link` or `{link, Opts}` will set a link to the spawned
569+ > process, just like [start_link/3,4,5](`start_link/3`).
564570""" .
565571-doc (#{since => <<" OTP 23.0" >>}).
566572-spec start_monitor (Module , Function , Args , Time , SpawnOpts ) -> {Ret , Mon } when
567573 Module :: module (),
568574 Function :: atom (),
569575 Args :: [term ()],
570576 Time :: timeout (),
571- SpawnOpts :: [start_spawn_option ()],
577+ SpawnOpts :: [spawn_option ()],
572578 Mon :: reference (),
573579 Ret :: term () | {error , Reason :: term ()}.
574580
575581start_monitor (M ,F ,A ,Timeout ,SpawnOpts ) when is_atom (M ),
576582 is_atom (F ),
577583 is_list (A ) ->
578- ? VERIFY_NO_MONITOR_OPT ( M , F , A , Timeout , SpawnOpts ),
584+ SpawnOpts1 = ensure_spawn_option ( monitor , SpawnOpts ),
579585 sync_start_monitor (
580- ? MODULE :spawn_opt (M , F , A , [ monitor | SpawnOpts ] ), Timeout ).
586+ ? MODULE :spawn_opt (M , F , A , SpawnOpts1 ), Timeout ).
581587
582588sync_start_monitor ({Pid , Ref }, Timeout ) ->
583589 receive
@@ -587,7 +593,7 @@ sync_start_monitor({Pid, Ref}, Timeout) ->
587593 flush_EXIT (Pid ),
588594 self () ! await_DOWN (Pid , Ref ),
589595 {Return , Ref };
590- {'DOWN' , Ref , process , Pid , Reason } = Down ->
596+ {_ , Ref , process , Pid , Reason } = Down ->
591597 flush_EXIT (Pid ),
592598 self () ! Down ,
593599 {{error , Reason }, Ref }
@@ -597,6 +603,18 @@ sync_start_monitor({Pid, Ref}, Timeout) ->
597603 {{error , timeout }, Ref }
598604 end .
599605
606+ % % Adds the given Opt atom to the given SpawnOpts list
607+ % % if it is not already contained either in plain form
608+ % % or as the first element of a tuple.
609+ ensure_spawn_option (Opt , [Opt | _ ] = SpawnOpts ) ->
610+ SpawnOpts ;
611+ ensure_spawn_option (Opt , [SpawnOpt | _ ] = SpawnOpts )
612+ when Opt =:= element (1 , SpawnOpt ) ->
613+ SpawnOpts ;
614+ ensure_spawn_option (Opt , [SpawnOpt | SpawnOpts ]) ->
615+ [SpawnOpt | ensure_spawn_option (Opt , SpawnOpts )];
616+ ensure_spawn_option (Opt , []) ->
617+ [Opt ].
600618
601619% % We regard the existence of an {'EXIT', Pid, _} message
602620% % as proof enough that there was a link that fired and
@@ -620,7 +638,7 @@ kill_flush_EXIT(Pid) ->
620638
621639await_DOWN (Pid , Ref ) ->
622640 receive
623- {'DOWN' , Ref , process , Pid , _ } = Down ->
641+ {_ , Ref , process , Pid , _ } = Down ->
624642 Down
625643 end .
626644
0 commit comments