Skip to content

Commit

Permalink
stdlib: add consistent naming to gen_XXX
Browse files Browse the repository at this point in the history
  • Loading branch information
kikofernandez committed Jun 12, 2023
1 parent 944ce98 commit 5965f42
Show file tree
Hide file tree
Showing 11 changed files with 123 additions and 126 deletions.
4 changes: 2 additions & 2 deletions lib/common_test/src/test_server.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2791,7 +2791,7 @@ peer_name(Module, TestCase) ->
%% Command line arguments passed
-spec start_peer([string()] | peer:start_options() | #{ start_cover => boolean() },
atom() | string(), TestCase :: atom() | string()) ->
{ok, gen_statem:server_ref(), node()} | {error, term()}.
{ok, gen_statem:process_ref(), node()} | {error, term()}.
start_peer(Args, Module, TestCase) when is_list(Args) ->
start_peer(#{args => Args, name => peer_name(Module, TestCase)}, Module);

Expand All @@ -2805,7 +2805,7 @@ start_peer(Opts, Module, TestCase) ->
-spec start_peer([string()] | peer:start_options() | #{ start_cover => boolean() },
atom() | string(), TestCase :: atom() | string(),
Release :: string(), OutDir :: file:filename()) ->
{ok, gen_statem:server_ref(), node()} | {error, term()} | not_available.
{ok, gen_statem:process_ref(), node()} | {error, term()} | not_available.
start_peer(Args, Module, TestCase, Release, OutDir) when is_list(Args) ->
start_peer(#{args => Args}, Module, TestCase, Release, OutDir);
start_peer(Opts, Module, TestCase, Release, OutDir) ->
Expand Down
2 changes: 1 addition & 1 deletion lib/dialyzer/test/small_SUITE_data/results/gencall
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@

gencall.erl:10:3: Call to missing or unexported function gen_server:handle_cast/2
gencall.erl:5:1: Function f/0 has no local return
gencall.erl:6:34: The call gen_server:call(pid(),'request',{'not_a_timeout'}) breaks the contract (ServerRef::server_ref(),Request::term(),Timeout::timeout()) -> Reply::term()
gencall.erl:6:34: The call gen_server:call(pid(),'request',{'not_a_timeout'}) breaks the contract (ServerRef::process_ref(),Request::term(),Timeout::timeout()) -> Reply::term()
gencall.erl:7:3: Call to missing or unexported function ets:lookup/3
gencall.erl:9:3: Call to missing or unexported function gencall:foo/0
2 changes: 1 addition & 1 deletion lib/stdlib/doc/src/gen_event.xml
Original file line number Diff line number Diff line change
Expand Up @@ -142,7 +142,7 @@ gen_event:stop -----> Module:terminate/2
</datatype>

<datatype>
<name name="sup_ref"/>
<name name="process_ref"/>
</datatype>

<datatype>
Expand Down
18 changes: 9 additions & 9 deletions lib/stdlib/doc/src/gen_server.xml
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,7 @@ gen_server:abcast -----> Module:handle_cast/2

<datatypes>
<datatype>
<name name="server_name"/>
<name name="process_name"/>
<desc>
<p>
Name specification to use when starting a <c>gen_server</c>.
Expand All @@ -132,8 +132,8 @@ gen_server:abcast -----> Module:handle_cast/2
<seemfa marker="#start_monitor/3"><c>start_monitor/3,4</c></seemfa>,
<seemfa marker="#enter_loop/3"><c>enter_loop/3,4,5</c></seemfa>,
and the type
<seetype marker="#server_ref"><c>server_ref()</c></seetype>
is an alias to <seetype marker="stdlib:supervisor#sup_name"><c>supervisor:process_name()</c></seetype>.
<seetype marker="#process_ref"><c>process_ref()</c></seetype>
is an alias to <seetype marker="stdlib:supervisor#process_name"><c>supervisor:process_name()</c></seetype>.
</p>
<taglist>
<tag><c>{local,LocalName}</c></tag>
Expand Down Expand Up @@ -174,7 +174,7 @@ gen_server:abcast -----> Module:handle_cast/2
</datatype>

<datatype>
<name name="server_ref"/>
<name name="process_ref"/>
<desc>
<p>
Server specification to use when addressing
Expand All @@ -186,7 +186,7 @@ gen_server:abcast -----> Module:handle_cast/2
<seemfa marker="#wait_response/2"><c>wait_response/2</c></seemfa>,
<seemfa marker="#stop/1"><c>stop/2,3</c></seemfa>
and the type
<seetype marker="#server_name"><c>server_name()</c></seetype>
<seetype marker="#process_name"><c>process_name()</c></seetype>
above.
</p>
<p>It can be:</p>
Expand Down Expand Up @@ -556,7 +556,7 @@ gen_server:abcast -----> Module:handle_cast/2
</p>
<p>
See also <c><anno>ServerRef</anno></c>'s type
<seetype marker="#server_ref"><c>server_ref()</c></seetype>.
<seetype marker="#process_ref"><c>process_ref()</c></seetype>.
</p>
<p>
<c><anno>Request</anno></c> is any term that is passed as the
Expand Down Expand Up @@ -691,7 +691,7 @@ gen_server:abcast -----> Module:handle_cast/2
</p>
<p>
See also <c><anno>ServerRef</anno></c>'s type
<seetype marker="#server_ref"><c>server_ref()</c></seetype>.
<seetype marker="#process_ref"><c>process_ref()</c></seetype>.
</p>
<p>
<c><anno>Request</anno></c> is any term that is passed as
Expand Down Expand Up @@ -1199,7 +1199,7 @@ gen_server:abcast -----> Module:handle_cast/2
</p>
<p>
See the type
<seetype marker="#server_ref"><c>server_ref()</c></seetype>
<seetype marker="#process_ref"><c>process_ref()</c></seetype>
for the possible values for <c><anno>ServerRef</anno></c>.
</p>
<p>
Expand Down Expand Up @@ -1280,7 +1280,7 @@ gen_server:abcast -----> Module:handle_cast/2
Using the argument <c><anno>ServerName</anno></c>
creates a <c>gen_server</c> with a registered name.
See type
<seetype marker="#server_name"><c>server_name()</c></seetype>
<seetype marker="#process_name"><c>process_name()</c></seetype>
for different name registrations.
If no <c><anno>ServerName</anno></c> is provided,
the <c>gen_server</c> process is not registered.
Expand Down
26 changes: 13 additions & 13 deletions lib/stdlib/doc/src/gen_statem.xml
Original file line number Diff line number Diff line change
Expand Up @@ -512,26 +512,26 @@ handle_event(_, _, State, Data) ->

<datatypes>
<datatype>
<name name="server_name"/>
<name name="process_name"/>
<desc>
<p>
Name specification to use when starting
a <c>gen_statem</c> server. See
<seemfa marker="#start_link/3"><c>start_link/3</c></seemfa>
and
<seetype marker="#server_ref"><c>server_ref()</c></seetype>
<seetype marker="#process_ref"><c>process_ref()</c></seetype>
below.
</p>
</desc>
</datatype>
<datatype>
<name name="server_ref"/>
<name name="process_ref"/>
<desc>
<p>
Server specification to use when addressing
a <c>gen_statem</c> server.
See <seemfa marker="#call/2"><c>call/2</c></seemfa> and
<seetype marker="#server_name"><c>server_name()</c></seetype>
<seetype marker="#process_name"><c>process_name()</c></seetype>
above.
</p>
<p>It can be:</p>
Expand Down Expand Up @@ -1756,7 +1756,7 @@ handle_event(_, _, State, Data) ->
<desc>
<p>
Makes a synchronous call to the <c>gen_statem</c>
<seetype marker="#server_ref"><c><anno>ServerRef</anno></c></seetype>
<seetype marker="#process_ref"><c><anno>ServerRef</anno></c></seetype>
by sending a request
and waiting until its reply arrives.
The <c>gen_statem</c> calls the
Expand Down Expand Up @@ -1820,7 +1820,7 @@ handle_event(_, _, State, Data) ->
<desc>
<p>
Sends an asynchronous event to the <c>gen_statem</c>
<seetype marker="#server_ref"><c><anno>ServerRef</anno></c></seetype>
<seetype marker="#process_ref"><c><anno>ServerRef</anno></c></seetype>
and returns <c>ok</c> immediately,
ignoring if the destination node or <c>gen_statem</c>
does not exist.
Expand Down Expand Up @@ -1940,7 +1940,7 @@ handle_event(_, _, State, Data) ->
The same as
<seemfa marker="#enter_loop/6"><c>enter_loop/6</c></seemfa>
with <c>Actions = []</c> except that no
<seetype marker="#server_name"><c>server_name()</c></seetype>
<seetype marker="#process_name"><c>process_name()</c></seetype>
must have been registered. This creates an anonymous server.
</p>
</desc>
Expand All @@ -1955,7 +1955,7 @@ handle_event(_, _, State, Data) ->
the same as
<seemfa marker="#enter_loop/6"><c>enter_loop/6</c></seemfa>
except that no
<seetype marker="#server_name"><c>server_name()</c></seetype>
<seetype marker="#process_name"><c>process_name()</c></seetype>
must have been registered and
<c>Actions = <anno>Server_or_Actions</anno></c>.
This creates an anonymous server.
Expand Down Expand Up @@ -2000,11 +2000,11 @@ handle_event(_, _, State, Data) ->
server is created just as when using
<seemfa marker="#start_link/3"><c>start[_link|_monitor]/3</c></seemfa>.
If <c><anno>Server</anno></c> is a
<seetype marker="#server_name"><c>server_name()</c></seetype>
<seetype marker="#process_name"><c>process_name()</c></seetype>
a named server is created just as when using
<seemfa marker="#start_link/4"><c>start[_link|_monitor]/4</c></seemfa>.
However, the
<seetype marker="#server_name"><c>server_name()</c></seetype>
<seetype marker="#process_name"><c>process_name()</c></seetype>
name must have been registered accordingly
<em>before</em> this function is called.
</p>
Expand All @@ -2022,7 +2022,7 @@ handle_event(_, _, State, Data) ->
<seeerl marker="proc_lib"><c>proc_lib</c></seeerl>
start function, or if it is not registered
according to
<seetype marker="#server_name"><c>server_name()</c></seetype>.
<seetype marker="#process_name"><c>process_name()</c></seetype>.
</p>
</desc>
</func>
Expand Down Expand Up @@ -2396,7 +2396,7 @@ handle_event(_, _, State, Data) ->
</p>
<p>
<c><anno>ServerName</anno></c> specifies the
<seetype marker="#server_name"><c>server_name()</c></seetype>
<seetype marker="#process_name"><c>process_name()</c></seetype>
to register for the <c>gen_statem</c>.
If the <c>gen_statem</c> is started with <c>start_link/3</c>,
no <c><anno>ServerName</anno></c> is provided and
Expand Down Expand Up @@ -2546,7 +2546,7 @@ handle_event(_, _, State, Data) ->
<desc>
<p>
Orders the <c>gen_statem</c>
<seetype marker="#server_ref"><c><anno>ServerRef</anno></c></seetype>
<seetype marker="#process_ref"><c><anno>ServerRef</anno></c></seetype>
to exit with the specified <c><anno>Reason</anno></c>
and waits for it to terminate.
The <c>gen_statem</c> calls
Expand Down
6 changes: 3 additions & 3 deletions lib/stdlib/doc/src/supervisor.xml
Original file line number Diff line number Diff line change
Expand Up @@ -402,10 +402,10 @@ child_spec() = #{id => child_id(), % mandatory
<seeerl marker="#sup_flags">above</seeerl>.</p></desc>
</datatype>
<datatype>
<name name="sup_ref"/>
<name name="process_ref"/>
</datatype>
<datatype>
<name name="sup_name"/>
<name name="process_name"/>
</datatype>
<datatype>
<name name="worker"/>
Expand Down Expand Up @@ -609,7 +609,7 @@ child_spec() = #{id => child_id(), % mandatory
<fsummary>Create a supervisor process.</fsummary>
<type name="startlink_ret"/>
<type name="startlink_err"/>
<type name="sup_name"/>
<type name="process_name"/>
<desc>
<p>Creates a supervisor process as part of a supervision tree.
For example, the function ensures that the supervisor is linked to
Expand Down
27 changes: 12 additions & 15 deletions lib/stdlib/src/gen.erl
Original file line number Diff line number Diff line change
Expand Up @@ -54,9 +54,7 @@
request_id_collection/0]).

-type linkage() :: 'monitor' | 'link' | 'nolink'.
-type emgr_name() :: {'local', atom()}
| {'global', term()}
| {'via', Module :: module(), Name :: term()}.
-type process_name() :: proc_lib:process_name().

-type start_ret() :: {'ok', pid()}
| {'ok', {pid(), reference()}}
Expand All @@ -65,8 +63,7 @@

-type option() :: proc_lib:option().

-type server_ref() :: pid() | atom() | {atom(), node()}
| {global, term()} | {via, module(), term()}.
-type process_ref() :: proc_lib:process_ref().

-opaque reply_tag() :: % As accepted by reply/2
reference()
Expand Down Expand Up @@ -97,7 +94,7 @@
%% The 'already_started' is returned only if Name is given
%%-----------------------------------------------------------------

-spec start(module(), linkage(), emgr_name(), module(), term(), [option()]) ->
-spec start(module(), linkage(), process_name(), module(), term(), [option()]) ->
start_ret().

start(GenMod, LinkP, Name, Mod, Args, Options) ->
Expand Down Expand Up @@ -286,7 +283,7 @@ get_node(Process) ->
node(Process)
end.

-spec send_request(Name::server_ref(), Tag::term(), Request::term()) ->
-spec send_request(Name::process_ref(), Tag::term(), Request::term()) ->
request_id().
send_request(Process, Tag, Request) when is_pid(Process) ->
do_send_request(Process, Tag, Request);
Expand All @@ -300,7 +297,7 @@ send_request(Process, Tag, Request) ->
Mref
end.

-spec send_request(Name::server_ref(), Tag::term(), Request::term(),
-spec send_request(Name::process_ref(), Tag::term(), Request::term(),
Label::term(), ReqIdCol::request_id_collection()) ->
request_id_collection().
send_request(Process, Tag, Request, Label, ReqIdCol) when is_map(ReqIdCol) ->
Expand Down Expand Up @@ -331,7 +328,7 @@ do_send_request(Process, Tag, Request) ->
-spec wait_response(ReqId, Timeout) -> Result when
ReqId :: request_id(),
Timeout :: response_timeout(),
Resp :: {reply, Reply::term()} | {error, {Reason::term(), server_ref()}},
Resp :: {reply, Reply::term()} | {error, {Reason::term(), process_ref()}},
Result :: Resp | 'timeout'.

wait_response(ReqId, Timeout) ->
Expand All @@ -350,7 +347,7 @@ wait_response(ReqId, Timeout) ->
ReqIdCol :: request_id_collection(),
Timeout :: response_timeout(),
Delete :: boolean(),
Resp :: {reply, Reply::term()} | {error, {Reason::term(), server_ref()}},
Resp :: {reply, Reply::term()} | {error, {Reason::term(), process_ref()}},
Result :: {Resp, Label::term(), NewReqIdCol::request_id_collection()} |
'no_request' | 'timeout'.

Expand All @@ -373,7 +370,7 @@ wait_response(ReqIdCol, Timeout, Delete) when is_map(ReqIdCol),
-spec receive_response(ReqId, Timeout) -> Result when
ReqId :: request_id(),
Timeout :: response_timeout(),
Resp :: {reply, Reply::term()} | {error, {Reason::term(), server_ref()}},
Resp :: {reply, Reply::term()} | {error, {Reason::term(), process_ref()}},
Result :: Resp | 'timeout'.

receive_response(ReqId, Timeout) ->
Expand All @@ -398,7 +395,7 @@ receive_response(ReqId, Timeout) ->
ReqIdCol :: request_id_collection(),
Timeout :: response_timeout(),
Delete :: boolean(),
Resp :: {reply, Reply::term()} | {error, {Reason::term(), server_ref()}},
Resp :: {reply, Reply::term()} | {error, {Reason::term(), process_ref()}},
Result :: {Resp, Label::term(), NewReqIdCol::request_id_collection()}
| 'no_request' | 'timeout'.

Expand Down Expand Up @@ -427,9 +424,9 @@ receive_response(ReqIdCol, Timeout, Delete) when is_map(ReqIdCol),
-spec check_response(Msg::term(), ReqIdOrReqIdCol) -> Result when
ReqIdOrReqIdCol :: request_id() | request_id_collection(),
ReqIdResp :: {reply, Reply::term()} |
{error, {Reason::term(), server_ref()}},
{error, {Reason::term(), process_ref()}},
ReqIdColResp :: {{reply, Reply::term()}, Label::term()} |
{{error, {Reason::term(), server_ref()}}, Label::term()},
{{error, {Reason::term(), process_ref()}}, Label::term()},
Result :: ReqIdResp | ReqIdColResp | 'no_reply'.

check_response(Msg, ReqId) when is_reference(ReqId) ->
Expand All @@ -449,7 +446,7 @@ check_response(_, _) ->
Msg :: term(),
ReqIdCol :: request_id_collection(),
Delete :: boolean(),
Resp :: {reply, Reply::term()} | {error, {Reason::term(), server_ref()}},
Resp :: {reply, Reply::term()} | {error, {Reason::term(), process_ref()}},
Result :: {Resp, Label::term(), NewReqIdCol::request_id_collection()}
| 'no_request' | 'no_reply'.

Expand Down
Loading

0 comments on commit 5965f42

Please sign in to comment.