From 6f11e9b65094d6e72f4a6da3aac7e3206b6d9307 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Tue, 5 Nov 2024 11:01:09 +0100 Subject: [PATCH 01/17] diameter: Fix broken doc signatures --- lib/diameter/src/base/diameter_codec.erl | 4 ---- lib/diameter/src/compiler/diameter_make.erl | 17 +++++++---------- lib/diameter/src/transport/diameter_sctp.erl | 2 +- 3 files changed, 8 insertions(+), 15 deletions(-) diff --git a/lib/diameter/src/base/diameter_codec.erl b/lib/diameter/src/base/diameter_codec.erl index 4a8e124cc732..b662e80e52e6 100644 --- a/lib/diameter/src/base/diameter_codec.erl +++ b/lib/diameter/src/base/diameter_codec.erl @@ -286,8 +286,6 @@ Diameter messages. %% *the* encode. -doc """ -encode(Mod, Msg) -> Pkt - Encode a Diameter message. """. -doc(#{since => <<"OTP R15B03">>}). @@ -477,8 +475,6 @@ rec2msg(Mod, Rec) -> %% longer *the* decode. -doc """ -decode(Mod, Bin) -> Pkt - Decode a Diameter message. """. -doc(#{since => <<"OTP R15B03">>}). diff --git a/lib/diameter/src/compiler/diameter_make.erl b/lib/diameter/src/compiler/diameter_make.erl index 37c94294c879..95162a32b09d 100644 --- a/lib/diameter/src/compiler/diameter_make.erl +++ b/lib/diameter/src/compiler/diameter_make.erl @@ -91,13 +91,12 @@ Unrecognized options are silently ignored. %% two. -doc """ -codec(File :: iolist() | binary(), [Opt]) -> ok | {ok, [Out]} | {error, Reason} +Compile a single dictionary file. -Compile a single dictionary file. The input `File` can be either a path or a -literal dictionary, the occurrence of newline (ascii NL) or carriage return -(ascii CR) identifying the latter. `Opt` determines the format of the results -and whether they are written to file or returned, and can have the following -types. +The input `File` can be either a path or a literal dictionary, the occurrence +of newline (ascii NL) or carriage return (ascii CR) identifying the latter. +`Opt` determines the format of the results and whether they are written to +file or returned, and can have the following types. - **`parse | forms | erl | hrl`** - Specifies an output format. Whether the output is returned or written to file depends on whether or not option @@ -183,7 +182,7 @@ codec(File) -> %% Turn an orddict returned by dict/1-2 back into a dictionary. -doc """ -format(Parsed) -> iolist() +format(Parsed) Turns a parsed dictionary, as returned by `codec/2`, back into the dictionary format. @@ -200,7 +199,7 @@ format([?VERSION | Dict]) -> %% Reconstitute a dictionary without @inherits. -doc """ -flatten(Parsed) -> term() +flatten(Parsed) Reconstitute a parsed dictionary, as returned by `codec/2`, without using [`@inherits`](diameter_dict.md#inherits). That is, construct an equivalent @@ -224,8 +223,6 @@ flatten([?VERSION = V | Dict]) -> %% format_error/1 -doc """ -format_error(Reason) -> string() - Turn an error reason returned by `codec/2` into a readable string. """. -doc(#{since => <<"OTP 17.0">>}). diff --git a/lib/diameter/src/transport/diameter_sctp.erl b/lib/diameter/src/transport/diameter_sctp.erl index 0b652db150a2..2b23190a7ae4 100644 --- a/lib/diameter/src/transport/diameter_sctp.erl +++ b/lib/diameter/src/transport/diameter_sctp.erl @@ -161,7 +161,7 @@ be specified as the value of a transport_module option to %% --------------------------------------------------------------------------- -doc """ -start({Type, Ref}, Svc, [Opt]) -> {ok, Pid, [LAddr]} | {error, Reason} +start(TypeRef, Svc, Options) The start function required by `m:diameter_transport`. From 99ef10e636e3bb4b523e4aee51dabfede1652cd4 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Tue, 5 Nov 2024 11:01:20 +0100 Subject: [PATCH 02/17] eldap: Fix broken doc signatures --- lib/eldap/src/eldap.erl | 8 +------- 1 file changed, 1 insertion(+), 7 deletions(-) diff --git a/lib/eldap/src/eldap.erl b/lib/eldap/src/eldap.erl index ad60ca1b146a..dbeef02bd19d 100644 --- a/lib/eldap/src/eldap.erl +++ b/lib/eldap/src/eldap.erl @@ -1921,9 +1921,6 @@ get_head([H|Rest],Tail,Rhead) -> get_head(Rest,Tail,[H|Rhead]). %%% -------------------------------------------------------------------- -doc """ -paged_result_control(PageSize) -> {control, "1.2.840.113556.1.4.319", true, -binary()} - Paged results is an extension to the LDAP protocol specified by RFC2696 This function creates a control with the specified page size for use in @@ -1943,9 +1940,6 @@ paged_result_control(PageSize) when is_integer(PageSize) -> paged_result_control(PageSize, ""). -doc """ -paged_result_control(PageSize, Cookie) -> {control, "1.2.840.113556.1.4.319", -true, binary()} - Paged results is an extension to the LDAP protocol specified by RFC2696 This function creates a control with the specified page size and cookie for use @@ -1986,7 +1980,7 @@ paged_result_control(PageSize, Cookie) when is_integer(PageSize) -> %%% -------------------------------------------------------------------- -doc """ -paged_result_cookie(SearchResult) -> binary() +paged_result_cookie(SearchResult) Paged results is an extension to the LDAP protocol specified by RFC2696. From 370a2bd48acf1d0c20ec02302302dbe1691f9009 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Tue, 5 Nov 2024 11:01:35 +0100 Subject: [PATCH 03/17] et: Fix broken doc signatures --- lib/et/src/et.erl | 8 ------ lib/et/src/et_collector.erl | 52 +++++-------------------------------- lib/et/src/et_selector.erl | 6 ++--- lib/et/src/et_viewer.erl | 16 ++---------- 4 files changed, 11 insertions(+), 71 deletions(-) diff --git a/lib/et/src/et.erl b/lib/et/src/et.erl index 4122dabbd592..e8a36129f188 100644 --- a/lib/et/src/et.erl +++ b/lib/et/src/et.erl @@ -136,8 +136,6 @@ Interface module for the Event Trace (ET) application %%---------------------------------------------------------------------- -doc """ -trace_me(DetailLevel, FromTo, Label, Contents) -> hopefully_traced - Invokes `et:trace_me/5` with both `From` and `To` set to `FromTo`. """. -doc(#{since => <<"OTP R13B04">>}). @@ -151,8 +149,6 @@ trace_me(DetailLevel, FromTo, Label, Contents) ?MODULE:trace_me(DetailLevel, FromTo, FromTo, Label, Contents). -doc """ -trace_me(DetailLevel, From, To, Label, Contents) -> hopefully_traced - A function that is intended to be traced. This function is intended to be invoked at strategic places in user applications @@ -192,8 +188,6 @@ phone_home(DetailLevel, FromTo, Label, Contents) -> ?MODULE:trace_me(DetailLevel, FromTo, FromTo, Label, Contents). -doc """ -phone_home(DetailLevel, From, To, Label, Contents) -> hopefully_traced - These functions sends a signal to the outer space and the caller hopes that someone is listening. In other words, they invoke `et:trace_me/4` and `et:trace_me/5` respectively. @@ -219,8 +213,6 @@ report_event(DetailLevel, FromTo, Label, Contents) -> ?MODULE:trace_me(DetailLevel, FromTo, FromTo, Label, Contents). -doc """ -report_event(DetailLevel, From, To, Label, Contents) -> hopefully_traced - Deprecated functions which for the time being are kept for backwards compatibility. Invokes `et:trace_me/4` and `et:trace_me/5` respectively. """. diff --git a/lib/et/src/et_collector.erl b/lib/et/src/et_collector.erl index 6951dd48a2b9..7681103e590d 100644 --- a/lib/et/src/et_collector.erl +++ b/lib/et/src/et_collector.erl @@ -207,8 +207,6 @@ Interface module for the Event Trace (ET) application %% Reason = term() %%---------------------------------------------------------------------- -doc """ -start_link(Options) -> {ok, CollectorPid} | {error, Reason} - Start a collector process. The collector collects trace events and keeps them ordered by their timestamp. @@ -352,11 +350,9 @@ start_clients(CollectorPid, []) -> %% CollectorPid = pid() %%---------------------------------------------------------------------- -doc """ -stop(CollectorPid) -> ok - Stop a collector process. """. --spec stop(CollectorPid::pid()) -> ok. +-spec stop(pid()) -> ok. stop(CollectorPid) -> call(CollectorPid, stop). @@ -386,8 +382,6 @@ stop(CollectorPid) -> %% The options defaults to existing, write and keep. %%---------------------------------------------------------------------- -doc """ -save_event_file(CollectorPid, FileName, Options) -> ok | {error, Reason} - Save the events to a file. By default the currently stored events (existing) are written to a brand new @@ -528,8 +522,8 @@ report(_, Bad) -> exit({bad_event, Bad}). -doc(#{equiv => report_event/6}). --spec report_event(CollectorPid, DetailLevel, FromTo, Label, Contents) -> {ok, Continuation} when - CollectorPid :: pid(), +-spec report_event(Handle, DetailLevel, FromTo, Label, Contents) -> {ok, Continuation} when + Handle :: CollectorPid :: pid() | table_handle(), DetailLevel :: level(), FromTo :: actor(), Label :: term(), @@ -539,9 +533,6 @@ report_event(CollectorPid, DetailLevel, FromTo, Label, Contents) -> report_event(CollectorPid, DetailLevel, FromTo, FromTo, Label, Contents). -doc """ -report_event(Handle, DetailLevel, From, To, Label, Contents) -> {ok, -Continuation} | exit(Reason) - Report an event to the collector. All events are filtered thru the collector filter, which optionally may @@ -549,8 +540,8 @@ transform or discard the event. The first call should use the pid of the collector process as report handle, while subsequent calls should use the table handle. """. --spec report_event(CollectorPid, DetailLevel, From, To, Label, Contents) -> {ok, Continuation} when - CollectorPid :: pid(), +-spec report_event(Handle, DetailLevel, From, To, Label, Contents) -> {ok, Continuation} when + Handle :: CollectorPid :: pid() | table_handle(), DetailLevel :: level(), From :: actor(), To :: actor(), @@ -582,8 +573,6 @@ report_event(CollectorPid, DetailLevel, From, To, Label, Contents) %%---------------------------------------------------------------------- -doc """ -make_key(Type, Stuff) -> Key - Make a key out of an event record or an old key. """. -spec make_key(Handle, Stuff) -> Key when @@ -644,8 +633,6 @@ get_table_handle(CollectorPid) when is_pid(CollectorPid) -> %% Reason = term() %%---------------------------------------------------------------------- -doc """ -get_global_pid() -> CollectorPid | exit(Reason) - Return a the identity of the globally registered collector if there is any. """. -spec get_global_pid() -> CollectorPid :: pid(). @@ -671,8 +658,6 @@ get_global_pid() -> %% TracePattern = {report_module(), dbg_match_spec_match_spec()} %%---------------------------------------------------------------------- -doc """ -change_pattern(CollectorPid, RawPattern) -> {old_pattern, TracePattern} - Change active trace pattern globally on all trace nodes. """. -spec change_pattern(CollectorPid, RawPattern) -> {old_pattern, TracePattern} when @@ -709,11 +694,7 @@ change_pattern(CollectorPid, RawPattern) -> %% Val = term() %%---------------------------------------------------------------------- -doc """ -dict_insert(CollectorPid, Key, Val) -> okdict_insert(CollectorPid, {subscriber, -SubscriberPid}, Void) -> okdict_insert(CollectorPid, {filter, collector}, -FilterFun) -> ok - -Insert a dictionary entry and send a \{et, \{dict_insert, Key, Val\}\} tuple to +Insert a dictionary entry and send a `{et, {dict_insert, Key, Val}}` tuple to all registered subscribers. If the entry is a new subscriber, it will imply that the new subscriber process @@ -754,8 +735,6 @@ dict_insert(CollectorPid, Key, Val) -> %% Val = term() %%---------------------------------------------------------------------- -doc """ -dict_lookup(CollectorPid, Key) -> [Val] - Lookup a dictionary entry and return zero or one value. """. -spec dict_lookup(CollectorPid::pid(), Key::term()) -> [Val::term()]. @@ -781,8 +760,6 @@ dict_lookup(CollectorPid, Key) -> %% Key = term() %%---------------------------------------------------------------------- -doc """ -dict_delete(CollectorPid, Key) -> ok - Delete a dictionary entry and send a \{et, \{dict_delete, Key\}\} tuple to all registered subscribers. @@ -808,8 +785,6 @@ dict_delete(CollectorPid, Key) -> %% val() = term() %%---------------------------------------------------------------------- -doc """ -dict_match(CollectorPid, Pattern) -> [Match] - Match some dictionary entries """. -spec dict_match(CollectorPid::pid(), {KeyPattern, ValPattern}) -> [Match] when @@ -828,8 +803,6 @@ dict_match(CollectorPid, Pattern) -> %% Msg = term() %%---------------------------------------------------------------------- -doc """ -multicast(\_CollectorPid, Msg) -> ok - Sends a message to all registered subscribers. """. -spec multicast(CollectorPid :: pid(), Msg::term()) -> ok. @@ -851,9 +824,6 @@ multicast(CollectorPid, Msg) -> %% Pid = dbg_trace_client_pid() %%---------------------------------------------------------------------- -doc """ -start_trace_client(CollectorPid, Type, Parameters) -> file_loaded | -{trace_client_pid, pid()} | exit(Reason) - Load raw Erlang trace from a file, port or process. """. -spec start_trace_client(CollectorPid, Type, Parameter) -> file_loaded | {trace_client_pid, pid()} when @@ -920,11 +890,7 @@ monitor_trace_port(CollectorPid, Parameters) -> %% %% Short for iterate/5. %%---------------------------------------------------------------------- --doc """ -iterate(Handle, Prev, Limit) -> NewAcc - -Short for iterate(Handle, Prev, Limit, undefined, Prev) -> NewAcc -""". +-doc #{ equiv => iterate(Handle, Prev, Limit, undefined, Prev) }. -spec iterate(Handle, Prev, Limit) -> NewAcc when Handle :: CollectorPid | table_handle(), CollectorPid :: pid(), @@ -957,8 +923,6 @@ iterate(Handle, Prev, Limit) -> %% Acc = NewAcc = term() %%---------------------------------------------------------------------- -doc """ -iterate(Handle, Prev, Limit, Fun, Acc) -> NewAcc - Iterate over the currently stored events. Iterates over the currently stored events and applies a function for each event. @@ -1115,8 +1079,6 @@ incr(Val, Incr) -> %% table_handle() = record(table_handle) %%---------------------------------------------------------------------- -doc """ -clear_table(Handle) -> ok - Clear the event table. """. -spec clear_table(Handle) -> ok when diff --git a/lib/et/src/et_selector.erl b/lib/et/src/et_selector.erl index d231f24076c5..6f004be66000 100644 --- a/lib/et/src/et_selector.erl +++ b/lib/et/src/et_selector.erl @@ -52,7 +52,7 @@ %% integer() - explicit detail level of tracing %%---------------------------------------------------------------------- -doc """ -make_pattern(RawPattern) -> TracePattern +make_pattern(RawPattern) Makes a trace pattern suitable to feed change_pattern/1 @@ -115,7 +115,7 @@ make_pattern({Mod, Pattern}) when is_atom(Mod) -> %% accordingly with erlang:trace_pattern/2. %%---------------------------------------------------------------------- -doc """ -change_pattern(Pattern) -> ok +change_pattern(Pattern) Activates/deactivates tracing by changing the current trace pattern. @@ -219,8 +219,6 @@ error_to_exit({ok, _Res}) -> %% should be dropped %%---------------------------------------------------------------------- -doc """ -parse_event(Mod, ValidTraceData) -> false | true | {true, Event} - Transforms trace data and makes an event record out of it. See `erlang:trace/3` for more info about the semantics of the trace data. diff --git a/lib/et/src/et_viewer.erl b/lib/et/src/et_viewer.erl index 5b559350200a..3b4aac62d823 100644 --- a/lib/et/src/et_viewer.erl +++ b/lib/et/src/et_viewer.erl @@ -75,8 +75,6 @@ %% Reason = term() %%---------------------------------------------------------------------- -doc """ -file(FileName) -> {ok, ViewerPid} | {error, Reason} - Start a new event viewer and a corresponding collector and load them with trace events from a trace file. """. @@ -96,8 +94,6 @@ file(FileName) -> %%---------------------------------------------------------------------- -doc """ -start() -> ok - Simplified start of a sequence chart viewer with global tracing activated. Convenient to be used from the command line (erl -s et_viewer). @@ -110,8 +106,6 @@ start() -> %% start(Options) -> {ok, ViewerPid} | {error, Reason} %%---------------------------------------------------------------------- -doc """ -start(Options) -> ok - Start of a sequence chart viewer without linking to the parent process. """. -spec start(GUIorOptions) -> {ok, Viewer::pid()} | {error, term()} when @@ -185,12 +179,10 @@ start(Options, GUI) -> %% and returns false | true | {true, NewEvent}. %%---------------------------------------------------------------------- -doc """ -start_link(Options) -> {ok, ViewerPid} | {error, Reason} - Start a sequence chart viewer for trace events (messages/actions) -A filter_fun() takes an event record as sole argument and returns false | true | -\{true, NewEvent\}. +A filter_fun() takes an event record as sole argument and returns +`false | true | {true, NewEvent}`. If the `collector_pid` is `undefined` a new `et_collector` will be started with the following parameter settings: `parent_pid`, `event_order`, `trace_global`, @@ -240,8 +232,6 @@ start_link(Options, GUI) -> which_gui() -> wx. -doc """ -get_collector_pid(ViewerPid) -> CollectorPid - Returns the identifier of the collector process. """. -spec get_collector_pid(ViewerPid::pid()) -> pid(). @@ -256,8 +246,6 @@ get_collector_pid(ViewerPid) -> %% ViewerPid = pid() %%---------------------------------------------------------------------- -doc """ -stop(ViewerPid) -> ok - Stops a viewer process. """. -spec stop(ViewerPid::pid()) -> ok. From 6b3f7433462e3e2a668dd81fcf4bbc0c349f2bd1 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Tue, 5 Nov 2024 11:01:44 +0100 Subject: [PATCH 04/17] inets: Fix broken doc signatures --- lib/inets/src/http_lib/http_uri.erl | 10 ++-------- 1 file changed, 2 insertions(+), 8 deletions(-) diff --git a/lib/inets/src/http_lib/http_uri.erl b/lib/inets/src/http_lib/http_uri.erl index 9193940901f6..7e7eb5dc2a94 100644 --- a/lib/inets/src/http_lib/http_uri.erl +++ b/lib/inets/src/http_lib/http_uri.erl @@ -58,15 +58,11 @@ For more information about URI, see %%%========================================================================= -doc """ -encode(DecodedPart) -> EncodedPart +Performs percent encoding. > #### Warning {: .warning } > > Use `uri_string:quote/1` instead - -Performs percent encoding. - -[](){: #decode } """. -doc(#{since => <<"OTP R15B01">>}). -spec encode(Data) -> QuotedData when @@ -76,13 +72,11 @@ encode(Data) -> uri_string:quote(Data). -doc """ -decode(EncodedPart) -> DecodePart +Decodes a possibly percent encoded URI part > #### Warning {: .warning } > > Use `uri_string:unquote/1` instead - -Decodes a possibly percent encoded URI part """. -doc(#{since => <<"OTP R15B01">>}). -spec decode(QuotedData) -> Data when From dcd538fc55a0f23c650f0bcb7fd9dc552ae344a0 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Tue, 5 Nov 2024 11:01:54 +0100 Subject: [PATCH 05/17] megaco: Fix broken doc signatures --- lib/megaco/examples/meas/megaco_codec_meas.erl | 2 +- lib/megaco/examples/meas/megaco_codec_mstone1.erl | 8 +------- lib/megaco/examples/meas/megaco_codec_mstone2.erl | 2 +- lib/megaco/examples/meas/megaco_codec_transform.erl | 2 -- lib/megaco/src/flex/megaco_flex_scanner.erl | 12 ------------ lib/megaco/src/tcp/megaco_tcp.erl | 2 -- 6 files changed, 3 insertions(+), 25 deletions(-) diff --git a/lib/megaco/examples/meas/megaco_codec_meas.erl b/lib/megaco/examples/meas/megaco_codec_meas.erl index abc1663c830c..b5aa89631e7b 100644 --- a/lib/megaco/examples/meas/megaco_codec_meas.erl +++ b/lib/megaco/examples/meas/megaco_codec_meas.erl @@ -102,7 +102,7 @@ start() -> meas_init(1, ?DEFAULT_OPTS, ?DEFAULT_MESSAGE_PACKAGE, ?MEASURE_CODECS). -doc """ -start(MessagePackage) -> void() +start(MessagePackage) This function runs the measurement on all the _official_ codecs; pretty, compact, ber, per and erlang. diff --git a/lib/megaco/examples/meas/megaco_codec_mstone1.erl b/lib/megaco/examples/meas/megaco_codec_mstone1.erl index 3302920cdbe9..ef91214deadb 100644 --- a/lib/megaco/examples/meas/megaco_codec_mstone1.erl +++ b/lib/megaco/examples/meas/megaco_codec_mstone1.erl @@ -95,7 +95,7 @@ start(Factor) -> start(?DEFAULT_MESSAGE_PACKAGE, ?MSTONE_RUN_TIME, Factor). -doc """ -start(MessagePackage, Factor) -> void() +start(MessagePackage, Factor) This function starts the _mstone1_ performance test with all codec configs. `Factor` (defaults to `1`) processes are started for every supported codec @@ -134,8 +134,6 @@ start_flex(Factor) -> start_flex(?DEFAULT_MESSAGE_PACKAGE, ?MSTONE_RUN_TIME, Factor). -doc """ -start_flex(MessagePackage, Factor) -> void() - This function starts the _mstone1_ performance test with only the flex codec configs (i.e. `pretty` and `compact` with `flex`). The same number of processes are started as when running the standard test (using the `start/0,1` function). @@ -164,8 +162,6 @@ start_only_drv(Factor) -> start_only_drv(?DEFAULT_MESSAGE_PACKAGE, ?MSTONE_RUN_TIME, Factor). -doc """ -start_only_drv(MessagePackage, Factor) -> void() - This function starts the _mstone1_ performance test with only the driver using codec configs (i.e. `pretty` and `compact` with `flex`, and `ber` and `per` with `driver` and `erlang` with `compressed`). The same number of processes are @@ -195,8 +191,6 @@ start_no_drv(Factor) -> start_no_drv(?DEFAULT_MESSAGE_PACKAGE, ?MSTONE_RUN_TIME, Factor). -doc """ -start_no_drv(MessagePackage, Factor) -> void() - This function starts the _mstone1_ performance test with codec configs not using any drivers (i.e. `pretty` and `compact` without `flex`, `ber` and `per` without `driver` and `erlang` without `compressed`). The same number of processes are diff --git a/lib/megaco/examples/meas/megaco_codec_mstone2.erl b/lib/megaco/examples/meas/megaco_codec_mstone2.erl index 16ecf95f2153..34f245a42cc8 100644 --- a/lib/megaco/examples/meas/megaco_codec_mstone2.erl +++ b/lib/megaco/examples/meas/megaco_codec_mstone2.erl @@ -118,7 +118,7 @@ start() -> ?DEFAULT_RUN_TIME, ?DEFAULT_MODE, ?DEFAULT_MESSAGE_PACKAGE). -doc """ -start(MessagePackage) -> void() +start(MessagePackage) This function starts the _mstone2_ performance test with all codec configs. Processes are created dynamically. Each process make _one_ run through their diff --git a/lib/megaco/examples/meas/megaco_codec_transform.erl b/lib/megaco/examples/meas/megaco_codec_transform.erl index bc80e4f6a716..831252c61edd 100644 --- a/lib/megaco/examples/meas/megaco_codec_transform.erl +++ b/lib/megaco/examples/meas/megaco_codec_transform.erl @@ -140,8 +140,6 @@ export_messages() -> export_messages(?DEFAULT_MESSAGE_PACKAGE). -doc """ -export_messages(MessagePackage) -> void() - Export the messages in the `MessagePackage` (default is `time_test`). The output produced by this function is a directory structure with the following diff --git a/lib/megaco/src/flex/megaco_flex_scanner.erl b/lib/megaco/src/flex/megaco_flex_scanner.erl index 580c923c10d4..ffb1d0551f6e 100644 --- a/lib/megaco/src/flex/megaco_flex_scanner.erl +++ b/lib/megaco/src/flex/megaco_flex_scanner.erl @@ -55,8 +55,6 @@ explicitly disable this even when flex support this. Use -doc """ Return value of a successful (flex) scanner start. - -[](){: #start } """. -type megaco_ports() :: port() | tuple(). @@ -96,11 +94,7 @@ is_enabled() -> -dialyzer({nowarn_function, is_reentrant_enabled/0}). -doc """ -is_reentrant_enabled() -> Boolean - Is the flex scanner reentrant or not. - -[](){: #is_scanner_port } """. -spec is_reentrant_enabled() -> boolean(). is_reentrant_enabled() -> @@ -111,8 +105,6 @@ is_reentrant_enabled() -> -doc """ Checks if a port is a flex scanner port or not (useful when if a port exits). - -[](){: #scan } """. -spec is_scanner_port(Port, PortOrPorts) -> boolean() when Port :: port(), @@ -153,8 +145,6 @@ created (one for each scheduler). Note that the process that calls this function _must_ be permanent. If it dies, the port(s) will exit and the driver unload. - -[](){: #stop } """. -spec start() -> {ok, PortOrPorts} | {error, Reason} when PortOrPorts :: megaco_ports(), @@ -233,8 +223,6 @@ drv_name() -> -doc """ This function is used to stop the flex scanner. It also unloads the driver. - -[](){: #is_reentrant_enabled } """. -spec stop(PortOrPorts) -> stopped when PortOrPorts :: megaco_ports(). diff --git a/lib/megaco/src/tcp/megaco_tcp.erl b/lib/megaco/src/tcp/megaco_tcp.erl index 00931b4003e1..58cfca84eb2c 100644 --- a/lib/megaco/src/tcp/megaco_tcp.erl +++ b/lib/megaco/src/tcp/megaco_tcp.erl @@ -603,8 +603,6 @@ close(Socket) -> %% Description: Returns the inet socket %%----------------------------------------------------------------- -doc """ -socket(Handle) -> Socket - This function is used to convert a socket `handle()` to a inet `socket()`. """. From 25912db0aef38665de568321a9e2887db6bf6e53 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Tue, 5 Nov 2024 11:02:13 +0100 Subject: [PATCH 06/17] mnesia: Fix broken doc signatures --- lib/mnesia/src/mnesia_frag_hash.erl | 10 ---------- 1 file changed, 10 deletions(-) diff --git a/lib/mnesia/src/mnesia_frag_hash.erl b/lib/mnesia/src/mnesia_frag_hash.erl index 884dff141d49..1bdbb04467c7 100644 --- a/lib/mnesia/src/mnesia_frag_hash.erl +++ b/lib/mnesia/src/mnesia_frag_hash.erl @@ -66,8 +66,6 @@ nicely when new fragments are added. It is well suited for scalable hash tables. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -doc """ -init_state(Tab, State) -> NewState | abort(Reason) - Starts when a fragmented table is created with the function `mnesia:create_table/2` or when a normal (unfragmented) table is converted to be a fragmented table with `mnesia:change_table_frag/2`. @@ -97,8 +95,6 @@ convert_old_state({hash_state, N, P, L}) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -doc """ -add_frag(State) -> {NewState, IterFrags, AdditionalLockFrags} | abort(Reason) - To scale well, it is a good idea to ensure that the records are evenly distributed over all fragments, including the new one. @@ -138,8 +134,6 @@ add_frag(OldState) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -doc """ -del_frag(State) -> {NewState, IterFrags, AdditionalLockFrags} | abort(Reason) - `NewState` is stored as `hash_state` among the other `frag_properties`. As a part of the `del_frag` procedure, Mnesia iterates over all fragments @@ -181,8 +175,6 @@ del_frag(OldState) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -doc """ -key_to_frag_number(State, Key) -> FragNum | abort(Reason) - Starts whenever Mnesia needs to determine which fragment a certain record belongs to. It is typically started at `read`, `write`, and `delete`. """. @@ -212,8 +204,6 @@ key_to_frag_number(OldState, Key) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -doc """ -match_spec_to_frag_numbers(State, MatchSpec) -> FragNums | abort(Reason) - This function is called whenever Mnesia needs to determine which fragments that need to be searched for a `MatchSpec`. It is typically called by `select` and `match_object`. From b1b86a92469fe2b488d7f52a9d0a1a980b8aaa8e Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Tue, 5 Nov 2024 11:02:19 +0100 Subject: [PATCH 07/17] observer: Fix broken doc signatures --- lib/observer/src/etop.erl | 12 -------- lib/observer/src/observer.erl | 14 ++------- lib/observer/src/ttb.erl | 58 +++++------------------------------ 3 files changed, 9 insertions(+), 75 deletions(-) diff --git a/lib/observer/src/etop.erl b/lib/observer/src/etop.erl index 677b205571f3..807e7bd8a4cc 100644 --- a/lib/observer/src/etop.erl +++ b/lib/observer/src/etop.erl @@ -96,8 +96,6 @@ For details about Erlang Top, see the [User's Guide](etop_ug.md). -define(change_at_runtime_config,[lines,interval,sort,accumulate]). -doc """ -help() -> ok - Displays the help of `etop` and its options. """. -doc(#{since => <<"OTP R15B01">>}). @@ -130,8 +128,6 @@ help() -> ). -doc """ -stop() -> stop - Terminates `etop`. """. -spec stop() -> stop | not_started. @@ -142,8 +138,6 @@ stop() -> end. -doc """ -config(Key,Value) -> Result - Changes the configuration parameters of the tool during runtime. Allowed parameters are `lines`, `interval`, `accumulate`, and `sort`. """. @@ -169,8 +163,6 @@ check_runtime_config(accumulate,A) when A=:=true; A=:=false -> ok; check_runtime_config(_Key,_Value) -> error. -doc """ -dump(File) -> Result - Dumps the current display to a text file. """. -spec dump(File) -> ok | {error, Reason} when @@ -183,8 +175,6 @@ dump(File) -> end. -doc """ -start() -> ok - Starts `etop`. Notice that `etop` is preferably started with the `etop` script. """. -doc(#{since => <<"OTP R15B01">>}). @@ -193,8 +183,6 @@ start() -> start([]). -doc """ -start(Options) -> ok - Starts `etop`. To view the possible options, use `help/0`. """. -doc(#{since => <<"OTP R15B01">>}). diff --git a/lib/observer/src/observer.erl b/lib/observer/src/observer.erl index bd1d4f7ea40e..41cb30371146 100644 --- a/lib/observer/src/observer.erl +++ b/lib/observer/src/observer.erl @@ -33,8 +33,6 @@ For details about how to get started, see the [`User's Guide`](observer_ug.md). -export([start/0, start/1, start_and_wait/0, start_and_wait/1, stop/0]). -doc """ -start() -> ok - Starts the Observer GUI. To stop the tool, close the window or call `stop/0`. """. -doc(#{since => <<"OTP R15B">>}). @@ -43,12 +41,10 @@ start() -> observer_wx:start(). -doc """ -start(Node) -> ok - Starts the Observer GUI and tries to connect it to `Node`. """. -doc(#{since => <<"OTP 26.0">>}). --spec start(node()|[node()]) -> ok | {error, term()}. +-spec start(Node :: node()|[node()]) -> ok | {error, term()}. start(Node) when is_atom(Node) -> start([Node]); start([Node]) -> @@ -67,8 +63,6 @@ start([Node]) -> end. -doc """ -start_and_wait() -> ok - Starts the Observer GUI and only return when it is either stopped or the window is closed """. @@ -83,13 +77,11 @@ start_and_wait() -> end. -doc """ -start_and_wait(Node) -> ok - Starts the Observer GUI and only return when it is either stopped or the window is closed, connects it directly to `Node` like `start/1`. """. -doc(#{since => <<"OTP 26.0">>}). --spec start_and_wait(node()|[node()]) -> ok. +-spec start_and_wait(Node :: node()|[node()]) -> ok. start_and_wait(Node) when is_atom(Node) -> start_and_wait([Node]); start_and_wait(List) when is_list(List) -> @@ -101,8 +93,6 @@ start_and_wait(List) when is_list(List) -> end. -doc """ -stop() -> ok - Stops the Observer GUI. """. -doc(#{since => <<"OTP 26.0">>}). diff --git a/lib/observer/src/ttb.erl b/lib/observer/src/ttb.erl index 1c4228fbf9d0..d3e8d20602f8 100644 --- a/lib/observer/src/ttb.erl +++ b/lib/observer/src/ttb.erl @@ -104,8 +104,6 @@ parallel. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%% Shortcut -doc """ -start_trace(Nodes, Patterns, FlagSpec, Opts) -> Result - This function is a shortcut allowing to start a trace with one command. Each tuple in `Patterns` is converted to a list, which in turn is passed to `ttb:tpl/2,3,4`. @@ -143,15 +141,11 @@ start_trace(Nodes, Patterns, {Procs, Flags}, Options) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%% Open a trace port on all given nodes and create the meta data file --doc """ -tracer() -> Result - -Equivalent to [`tracer(node())`](`tracer/1`). -""". +-doc #{ equiv => tracer(node()) }. -spec tracer() -> {ok, [node()]} | {error, term()}. tracer() -> tracer(node()). -doc """ -tracer(Nodes) -> Result +tracer(Nodes) Handy shortcuts for common tracing settings. @@ -160,15 +154,13 @@ Handy shortcuts for common tracing settings. `dbg` is equivalent to [`tracer(node(),[{shell, only}])`](`tracer/2`). -Equivalent to [`tracer(Nodes,[])`](`tracer/2`). +`Nodes` is equivalent to [`tracer(Nodes,[])`](`tracer/2`). """. -spec tracer('shell' | 'dbg' | nodes()) -> {ok, [node()]} | {error, term()}. tracer(shell) -> tracer(node(), shell); tracer(dbg) -> tracer(node(), {shell, only}); tracer(Nodes) -> tracer(Nodes,[]). -doc """ -tracer(Nodes,Opts) -> Result - Starts a file trace port on all specified nodes and points the system tracer for sequential tracing to the same port. @@ -484,8 +476,6 @@ store(Func,Args) -> ets:insert(?history_table,{Last+1,{?MODULE,Func,Args}}). -doc """ -list_history() -> History - All calls to `ttb` is stored in the history. This function returns the current content of the history. Any entry can be reexecuted with [`run_history/1`](`run_history/1`) or stored in a configuration file with @@ -501,8 +491,6 @@ list_history() -> end. -doc """ -run_history(N) -> ok | {error, Reason} - Executes the specified entry or entries from the history list. To list history, use `list_history/0`. """. @@ -538,11 +526,7 @@ run_printed({M,F,A},Verbose) -> R = apply(M,F,A), Verbose andalso print_result(R). --doc """ -write_config(ConfigFile,Config) - -Equivalent to [`write_config(ConfigFile,Config,[])`](`write_config/3`). -""". +-doc #{ equiv => write_config(ConfigFile,Config,[]) }. -spec write_config(ConfigFile, Config) -> Result when ConfigFile :: file:filename(), Config :: all | [integer()] | [mfas()], @@ -551,8 +535,6 @@ write_config(ConfigFile,Config) -> write_config(ConfigFile,Config,[]). -doc """ -write_config(ConfigFile,Config,Opts) -> ok | {error,Reason} - Creates or extends a configuration file, which can be used for restoring a specific configuration later. @@ -614,8 +596,6 @@ check_config([Other|_Rest],_Acc) -> {error,{illegal_config,Other}}. -doc """ -list_config(ConfigFile) -> Config | {error,Reason} - Lists all entries in the specified configuration file. """. -spec list_config(ConfigFile) -> Result when @@ -635,8 +615,6 @@ read_config(B,Acc,N) -> read_config(Rest,[{N,{M,F,A}}|Acc],N+1). -doc """ -run_config(ConfigFile) -> ok | {error,Reason} - Executes all entries in the specified configuration file. Notice that the history of the last trace is always available in file `ttb_last_config`. """. @@ -655,8 +633,6 @@ run_config(ConfigFile) -> end. -doc """ -run_config(ConfigFile,NumList) -> ok | {error,Reason} - Executes selected entries from the specified configuration file. `NumList` is a list of integers pointing out the entries to be executed. @@ -701,8 +677,6 @@ arg_list([A1|A],Acc) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%% Set trace flags on processes -doc """ -p(Item,Flags) -> Return - Sets the specified trace flags on the specified processes or ports. Flag `timestamp` is always turned on. @@ -820,7 +794,7 @@ tpl(A,B,C) -> dbg:tpl(A,B,ms(C)). -doc """ -tpl(Module [, Function [, Arity]], MatchSpec) +tpl(Module, Function, Arity, MatchSpec) These functions are to be used with trace flag `call`, `send`, and `'receive'` for setting and clearing trace patterns. @@ -1037,16 +1011,10 @@ fix_dot(FunStr) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%% Support for sequential trace --doc """ -seq_trigger_ms() -> MatchSpec - -Equivalent to [`seq_trigger_ms(all)`](`seq_trigger_ms/1`). -""". +-doc #{ equiv => seq_trigger_ms(all) }. -spec seq_trigger_ms() -> match_spec(). seq_trigger_ms() -> seq_trigger_ms(all). -doc """ -seq_trigger_ms(Flags) -> MatchSpec - A match specification can turn on or off sequential tracing. This function returns a match specification, which turns on sequential tracing with the specified `Flags`. @@ -1126,16 +1094,12 @@ no_store_write_trace_info(Key,What) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%% Stop tracing on all nodes -doc """ -stop() - Equivalent to [`stop([])`](`stop/1`). """. -spec stop() -> stopped | {stopped, Dir::file:filename()}. stop() -> stop([]). -doc """ -stop(Opts) -> stopped | {stopped, Dir} - Stops tracing on all nodes. Logs and trace information files are sent to the trace control node and stored in a directory named `ttb_upload_FileName-Timestamp`, where `Filename` is the one provided with @@ -1563,8 +1527,6 @@ write_info(Nodes,PI,Traci) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%% Format binary trace logs -doc """ -get_et_handler() - Returns the `et` handler, which can be used with [`format/2`](`format/2`) or [`tracer/2`](`tracer/2`). @@ -1577,18 +1539,12 @@ Example: `ttb:format(Dir, [{handler, ttb:get_et_handler()}])`. get_et_handler() -> {fun ttb_et:handler/4, initial}. --doc """ -format(File) - -Equivalent to [`format(File,[])`](`format/2`). -""". +-doc #{equiv => format(Files, []) }. -spec format(Files) -> ok | {error, term()} when Files :: [file:filename()] | file:filename(). format(Files) -> format(Files,[]). -doc """ -format(File,Options) -> ok | {error, Reason} - Reads the specified binary trace log(s). The logs are processed in the order of their time stamps as long as option `disable_sort` is not specified. From 116da9c7a4755c48ece722a4ac32cb1dcbb6fa2b Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Tue, 5 Nov 2024 11:02:26 +0100 Subject: [PATCH 08/17] snmp: Fix broken doc signatures --- lib/snmp/src/agent/snmp_generic.erl | 9 ++------- 1 file changed, 2 insertions(+), 7 deletions(-) diff --git a/lib/snmp/src/agent/snmp_generic.erl b/lib/snmp/src/agent/snmp_generic.erl index 827ec4d348d2..5adab4d477df 100644 --- a/lib/snmp/src/agent/snmp_generic.erl +++ b/lib/snmp/src/agent/snmp_generic.erl @@ -21,8 +21,6 @@ -moduledoc """ Generic Functions for Implementing SNMP Objects in a Database -[](){: #description } - The module `snmp_generic` contains generic functions for implementing tables (and variables) using the SNMP built-in database or Mnesia. These default functions are used if no instrumentation function is provided for a managed @@ -332,7 +330,7 @@ table_set_element(NameDb, RowIndex, Col, NewVal) -> snmpa_local_db:table_set_elements(NameDb, RowIndex, [{Col, NewVal}]). -doc """ -table_set_elements(NameDb, RowIndex, Cols) -> bool() +table_set_elements(NameDb, RowIndex, Cols) Sets the elements in `Cols` to the row specified by `RowIndex`. No checks are performed on the new values. @@ -348,7 +346,7 @@ table_set_elements(NameDb, RowIndex, Cols) -> % ret true snmpa_local_db:table_set_elements(NameDb, RowIndex, Cols). -doc """ -table_next(NameDb, RestOid) -> RowIndex | endOfTable +table_next(NameDb, RestOid) Finds the indices of the next row in the table. `RestOid` does not have to specify an existing row. @@ -1019,10 +1017,7 @@ collect_length(N, [El | Rest], Rts) -> %% Returns true or false. %%------------------------------------------------------------------ -doc """ -table_row_exists(NameDb, RowIndex) -> bool() - Checks if a row in a table exists. - """. table_row_exists(NameDb, RowIndex) -> case table_get_element(NameDb, RowIndex, 1) of From 0f5ec184e97f4ebae5376bcdc88e55098b52165e Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Tue, 5 Nov 2024 11:02:32 +0100 Subject: [PATCH 09/17] ssh: Fix broken doc signatures --- lib/ssh/src/ssh.erl | 6 +----- lib/ssh/src/ssh_client_channel.erl | 27 +++++++++------------------ lib/ssh/src/ssh_connection.erl | 2 +- 3 files changed, 11 insertions(+), 24 deletions(-) diff --git a/lib/ssh/src/ssh.erl b/lib/ssh/src/ssh.erl index 4b078a7b8901..b8f5957ac09d 100644 --- a/lib/ssh/src/ssh.erl +++ b/lib/ssh/src/ssh.erl @@ -322,8 +322,6 @@ connect(_HostOrSocket, PortOrOptions, OptionsOrTimeout) -> bad_arg(PortOrOptions, OptionsOrTimeout). -doc """ -connect(Host, Port, Options, NegotiationTimeout) -> Result - Connects to an SSH server at the `Host` on `Port`. As an alternative, an already open TCP socket could be passed to the function in @@ -560,7 +558,7 @@ daemon(Socket, UserOptions) -> -doc """ -daemon(HostAddress, Port, Options) -> Result +daemon(HostAddress, Port, Options) Starts a server listening for SSH connections on the given port. If the `Port` is 0, a random free port is selected. See `daemon_info/1` about how to find the @@ -894,8 +892,6 @@ shell_socket(Socket, Options) -> -doc """ -shell(Host, Port, Options) -> Result - Connects to an SSH server at `Host` and `Port` (defaults to 22) and starts an interactive shell on that remote host. diff --git a/lib/ssh/src/ssh_client_channel.erl b/lib/ssh/src/ssh_client_channel.erl index 17464ab86be5..909561df54b1 100644 --- a/lib/ssh/src/ssh_client_channel.erl +++ b/lib/ssh/src/ssh_client_channel.erl @@ -22,16 +22,6 @@ -module(ssh_client_channel). -moduledoc """ -\-behaviour(ssh_client_channel). (Replaces ssh_channel) - -> #### Note {: .info } -> -> This module replaces ssh_channel. -> -> The old module is still available for compatibility, but should not be used -> for new programs. The old module will not be maintained except for some error -> corrections - SSH services (clients and servers) are implemented as channels that are multiplexed over an SSH connection and communicates over the [SSH Connection Protocol](http://www.ietf.org/rfc/rfc4254.txt). This module @@ -43,6 +33,14 @@ be part of a supervisor tree. This is a requirement of channel processes implementing a subsystem that will be added to the `ssh` applications supervisor tree. +> #### Note {: .info } +> +> This module replaces ssh_channel. +> +> The old module is still available for compatibility, but should not be used +> for new programs. The old module will not be maintained except for some error +> corrections + > #### Note {: .info } > > When implementing a `ssh` subsystem for daemons, use @@ -216,8 +214,6 @@ call(ChannelPid, Msg) -> call(ChannelPid, Msg, infinity). -doc """ -call(ChannelRef, Msg, Timeout) -> Reply | {error, Reason} - Makes a synchronous call to the channel process by sending a message and waiting until a reply arrives, or a time-out occurs. The channel calls [Module:handle_call/3](`c:handle_call/3`) to handle the message. If the channel @@ -248,8 +244,6 @@ call(ChannelPid, Msg, TimeOute) -> end. -doc """ -cast(ChannelRef, Msg) -> ok - Sends an asynchronous message to the channel process and returns ok immediately, ignoring if the destination node or channel process does not exist. The channel calls [Module:handle_cast/2](`c:handle_cast/2`) to handle the message. @@ -307,9 +301,6 @@ start(ConnectionManager, ChannelId, CallBack, CbInitArgs, Exec) -> gen_server:start(?MODULE, [Options], []). -doc """ -start_link(SshConnection, ChannelId, ChannelCb, CbInitArgs) -> {ok, ChannelRef} -| {error, Reason} - Starts a process that handles an SSH channel. It is called internally, by the `ssh` daemon, or explicitly by the `ssh` client implementations. The behavior sets the `trap_exit` flag to `true`. @@ -363,7 +354,7 @@ enter_loop(State) -> %% Description: Initiates the server %%-------------------------------------------------------------------- -doc """ -init(Options) -> {ok, State} | {ok, State, Timeout} | {stop, Reason} +Initiates a client channel. The following options must be present: diff --git a/lib/ssh/src/ssh_connection.erl b/lib/ssh/src/ssh_connection.erl index a2c0357d43e3..fe8b5e942f68 100644 --- a/lib/ssh/src/ssh_connection.erl +++ b/lib/ssh/src/ssh_connection.erl @@ -499,7 +499,7 @@ send(ConnectionHandler, ChannelId, Type, Data) -> -doc """ -send(ConnectionRef, ChannelId, Type, Data, TimeOut) -> ok | Error +send(ConnectionRef, ChannelId, Type, Data, TimeOut) Is to be called by client- and server-channel processes to send data to each other. From 3f070db0e5e908635602c47a404ea4437375cafb Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Tue, 5 Nov 2024 11:02:38 +0100 Subject: [PATCH 10/17] stdlib: Fix broken doc signatures --- lib/stdlib/src/c.erl | 16 ++++------------ lib/stdlib/src/shell.erl | 2 -- 2 files changed, 4 insertions(+), 14 deletions(-) diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl index a0f84e1e4929..eb935688a41c 100644 --- a/lib/stdlib/src/c.erl +++ b/lib/stdlib/src/c.erl @@ -585,8 +585,6 @@ purge_and_load(Mod, File, Opts) -> -type cmd_line_arg() :: atom() | string(). -doc """ -lc(Files) -> ok - Compiles a list of files by calling `compile:file(File, [report_errors, report_warnings])` for each `File` in `Files`. @@ -1367,21 +1365,17 @@ get_uptime() -> %% Cross Reference Check %% -doc """ -xm(ModSpec) -> term() - Finds undefined functions, unused functions, and calls to deprecated functions in a module by calling `xref:m/1`. """. -spec xm(module() | file:filename()) -> XRefMRet :: term(). % xref:m/1 return -xm(M) -> - appcall(tools, xref, m, [M]). +xm(ModSpec) -> + appcall(tools, xref, m, [ModSpec]). %% %% Call yecc %% -doc """ -y(File) -> YeccRet - Generates an LALR-1 parser. Equivalent to: ```text @@ -1395,8 +1389,6 @@ For information about `File = name()`, see `m:filename`. For information about y(File) -> y(File, []). -doc """ -y(File, Options) -> YeccRet - Generates an LALR-1 parser. Equivalent to: ```text @@ -1407,8 +1399,8 @@ For information about `File = name()`, see `m:filename`. For information about `Options` and `YeccRet`, see [`yecc:file/2`](`yecc:file/1`). """. -spec y(file:name(), [yecc:option()]) -> YeccFileRet :: yecc:yecc_ret(). % yecc:file/2 return -y(File, Opts) -> - appcall(parsetools, yecc, file, [File, Opts]). +y(File, Options) -> + appcall(parsetools, yecc, file, [File, Options]). %% %% Avoid creating strong components in xref and dialyzer by making calls diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl index 45d04eddc5a0..8075e658cd76 100644 --- a/lib/stdlib/src/shell.erl +++ b/lib/stdlib/src/shell.erl @@ -1938,8 +1938,6 @@ results(L) when is_integer(L), L >= 0 -> set_env(stdlib, shell_saved_results, L, ?DEF_RESULTS). -doc """ -catch_exception(Bool) -> boolean() - Sets the exception handling of the evaluator process. The previous exception handling is returned. The default (`false`) is to kill the evaluator process when an exception occurs, which causes the shell to create a new evaluator From 1f93cbe6fb6b3463edad4a60f5309e19a29b7097 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Tue, 5 Nov 2024 11:02:43 +0100 Subject: [PATCH 11/17] wx: Fix broken doc signatures --- lib/wx/src/wx.erl | 74 +++++++++------------------------------- lib/wx/src/wx_object.erl | 39 ++------------------- 2 files changed, 20 insertions(+), 93 deletions(-) diff --git a/lib/wx/src/wx.erl b/lib/wx/src/wx.erl index eecd1682274c..1f68d7a23bbf 100644 --- a/lib/wx/src/wx.erl +++ b/lib/wx/src/wx.erl @@ -62,8 +62,6 @@ -module(wx). -moduledoc """ -A port of wxWidgets. - A port of [wxWidgets](http://www.wxwidgets.org/). This is the base api of [wxWidgets](http://www.wxwidgets.org/). This module @@ -174,14 +172,12 @@ Global (classless) functions are located in the wx_misc module. -type wx_enum() :: integer(). %% Constant defined in wx.hrl -type wx_wxHtmlLinkInfo() :: #wxHtmlLinkInfo{}. --doc "parent_class(X1) -> term()". --spec parent_class(wx_object()) -> boolean(). +-doc "". +-spec parent_class(Wx_ref :: wx_object()) -> boolean(). parent_class(_) -> true. %% Let the null pointers be sent down. %% @doc Starts a wx server. -doc """ -new() -> wx_object() - Starts a wx server. """. -spec new() -> wx_object(). @@ -194,10 +190,10 @@ new() -> %% be suppressed. The latter can be used as a silent test of whether %% wx is properly installed or not. -doc """ -new(Options::[Option]) -> wx_object() +Starts a wx server. -Starts a wx server. Option may be \{debug, Level\}, see debug/1. Or -\{silent_start, Bool\}, which causes error messages at startup to be suppressed. +Option may be `{debug, Level}`, see `debug/1`. Or `{silent_start, Bool}`, +which causes error messages at startup to be suppressed. The latter can be used as a silent test of whether wx is properly installed or not. """. @@ -214,8 +210,6 @@ new(Options) when is_list(Options) -> %% @doc Stops a wx server. -doc """ -destroy() -> ok - Stops a wx server. """. -spec destroy() -> 'ok'. @@ -228,8 +222,6 @@ destroy() -> %% Can be sent to other processes to allow them use this process wx environment. %% @see set_env/1 -doc """ -get_env() -> wx_env() - Gets this process's current wx environment. Can be sent to other processes to allow them use this process wx environment. @@ -245,12 +237,10 @@ get_env() -> %% @doc Sets the process wx environment, allows this process to use %% another process wx environment. -doc """ -set_env(Wx_env::wx_env()) -> ok - Sets the process wx environment, allows this process to use another process wx environment. """. --spec set_env(wx_env()) -> 'ok'. +-spec set_env(Wx_env :: wx_env()) -> 'ok'. set_env(#wx_env{sv=Pid} = Env) -> put(?WXE_IDENTIFIER, Env), %% put(opengl_port, Port), @@ -272,8 +262,6 @@ set_env(#wx_env{sv=Pid} = Env) -> %% The call always returns ok but will have sent any already received %% events to the calling process. -doc """ -subscribe_events() -> ok - Adds the calling process to the list of of processes that are listening to wx application events. @@ -296,8 +284,6 @@ subscribe_events() -> %% @doc Returns the null object -doc """ -null() -> wx_object() - Returns the null object """. -spec null() -> wx_object(). @@ -306,29 +292,23 @@ null() -> %% @doc Returns true if object is null, false otherwise -doc """ -is_null(Wx_ref::wx_object()) -> boolean() - Returns true if object is null, false otherwise """. --spec is_null(wx_object()) -> boolean(). +-spec is_null(Wx_ref :: wx_object()) -> boolean(). is_null(#wx_ref{ref=NULL}) -> NULL =:= 0. %% @doc Returns true if both arguments references the same object, false otherwise -doc """ -equal(Wx_ref::wx_object(), X2::wx_object()) -> boolean() - Returns true if both arguments references the same object, false otherwise """. --spec equal(wx_object(), wx_object()) -> boolean(). +-spec equal(Ref1 :: wx_object(), Ref2 :: wx_object()) -> boolean(). equal(#wx_ref{ref=Ref1}, #wx_ref{ref=Ref2}) -> Ref1 =:= Ref2. %% @doc Returns the object type -doc """ -getObjectType(Wx_ref::wx_object()) -> atom() - Returns the object type """. --spec getObjectType(wx_object()) -> atom(). +-spec getObjectType(Wx_ref :: wx_object()) -> atom(). getObjectType(#wx_ref{type=Type}) -> Type. @@ -336,8 +316,6 @@ getObjectType(#wx_ref{type=Type}) -> %% It is needed when using functions like wxWindow:findWindow/2, which %% returns a generic wxObject type. -doc """ -typeCast(Old::wx_object(), NewType::atom()) -> wx_object() - Casts the object to class NewType. It is needed when using functions like wxWindow:findWindow/2, which returns a generic wxObject type. """. @@ -355,8 +333,6 @@ typeCast(Old=#wx_ref{}, NewType) when is_atom(NewType) -> %% @see foldl/3 %% @see foldr/3 -doc """ -batch(Fun::function()) -> term() - Batches all `wx` commands used in the fun. Improves performance of the command processing by grabbing the wxWidgets thread so that no event processing will be done before the complete batch of commands is invoked. @@ -377,8 +353,6 @@ batch(Fun) -> %% @doc Behaves like {@link //stdlib/lists:foreach/2} but batches wx commands. See {@link batch/1}. -doc """ -foreach(Fun::function(), List::list()) -> ok - Behaves like `lists:foreach/2` but batches wx commands. See `batch/1`. """. -spec foreach(function(), list()) -> 'ok'. @@ -395,8 +369,6 @@ foreach(Fun, List) -> %% @doc Behaves like {@link //stdlib/lists:map/2} but batches wx commands. See {@link batch/1}. -doc """ -map(Fun::function(), List::list()) -> list() - Behaves like `lists:map/2` but batches wx commands. See `batch/1`. """. -spec map(function(), list()) -> list(). @@ -413,8 +385,6 @@ map(Fun, List) -> %% @doc Behaves like {@link //stdlib/lists:foldl/3} but batches wx commands. See {@link batch/1}. -doc """ -foldl(Fun::function(), Acc::term(), List::list()) -> term() - Behaves like `lists:foldl/3` but batches wx commands. See `batch/1`. """. -spec foldl(function(), term(), list()) -> term(). @@ -431,8 +401,6 @@ foldl(Fun, Acc, List) -> %% @doc Behaves like {@link //stdlib/lists:foldr/3} but batches wx commands. See {@link batch/1}. -doc """ -foldr(Fun::function(), Acc::term(), List::list()) -> term() - Behaves like `lists:foldr/3` but batches wx commands. See `batch/1`. """. -spec foldr(function(), term(), list()) -> term(). @@ -458,8 +426,6 @@ foldr(Fun, Acc, List) -> %% Use it carefully. -doc """ -create_memory(Size::integer()) -> wx_memory() - Creates a memory area (of Size in bytes) which can be used by an external library (i.e. opengl). It is up to the client to keep a reference to this object so it does not get garbage collected by erlang while still in use by the @@ -468,7 +434,7 @@ external library. This is far from erlang's intentional usage and can crash the erlang emulator. Use it carefully. """. --spec create_memory(integer()) -> wx_memory(). +-spec create_memory(Size :: integer()) -> wx_memory(). create_memory(Size) when Size > ?MIN_BIN_SIZE -> #wx_mem{bin = <<0:(Size*8)>>, size = Size}; create_memory(Size) -> @@ -476,11 +442,9 @@ create_memory(Size) -> %% @doc Returns the memory area as a binary. -doc """ -get_memory_bin(Wx_mem::wx_memory()) -> binary() - Returns the memory area as a binary. """. --spec get_memory_bin(wx_memory()) -> binary(). +-spec get_memory_bin(Wx_mem :: wx_memory()) -> binary(). get_memory_bin(#wx_mem{bin=Bin, size=Size}) when Size > ?MIN_BIN_SIZE -> Bin; get_memory_bin(#wx_mem{bin=Bin, size=Size}) -> @@ -490,12 +454,10 @@ get_memory_bin(#wx_mem{bin=Bin, size=Size}) -> %% @doc Saves the memory from deletion until release_memory/1 is called. %% If release_memory/1 is not called the memory will not be garbage collected. -doc """ -retain_memory(Wx_mem::wx_memory()) -> ok - -Saves the memory from deletion until release_memory/1 is called. If -release_memory/1 is not called the memory will not be garbage collected. +Saves the memory from deletion until `release_memory/1` is called. If +`release_memory/1` is not called the memory will not be garbage collected. """. --spec retain_memory(wx_memory()) -> 'ok'. +-spec retain_memory(Wx_mem :: wx_memory()) -> 'ok'. retain_memory(#wx_mem{}=Mem) -> case get(Mem) of {Mem, N} -> put(Mem, N+1); @@ -509,8 +471,8 @@ retain_memory(Bin) when is_binary(Bin) -> end, retain_memory(#wx_mem{bin=Bin, size=byte_size(Bin)}). --doc "release_memory(Wx_mem::wx_memory()) -> ok". --spec release_memory(wx_memory()) -> 'ok'. +-doc "Releases the memory retained by `retain_memory/1`". +-spec release_memory(Wx_mem :: wx_memory()) -> 'ok'. release_memory(#wx_mem{}=Mem) -> case erase(Mem) of 1 -> ok; @@ -524,7 +486,7 @@ release_memory(Bin) when is_binary(Bin) -> %% each call is printed on console. If Level is 'driver' each allocated %% object and deletion is printed on the console. -doc """ -debug(Debug::Level | [Level]) -> ok +debug(Level) Sets debug level. If debug level is 'verbose' or 'trace' each call is printed on console. If Level is 'driver' each allocated object and deletion is printed on @@ -571,8 +533,6 @@ set_debug(Level) when is_integer(Level) -> %% @doc Starts a Wx demo if examples directory exists and is compiled -doc """ -demo() -> ok | {error, atom()} - Starts a Wx demo if examples directory exists and is compiled """. -spec demo() -> 'ok' | {'error', atom()}. diff --git a/lib/wx/src/wx_object.erl b/lib/wx/src/wx_object.erl index d5f681fbd360..cbd2dc499403 100644 --- a/lib/wx/src/wx_object.erl +++ b/lib/wx/src/wx_object.erl @@ -110,8 +110,6 @@ -module(wx_object). -moduledoc """ -wx_object - Generic wx object behaviour. - wx_object - Generic wx object behaviour This is a behaviour module that can be used for "sub classing" wx objects. It @@ -297,8 +295,6 @@ start(Mod, Args, Options) -> %% @doc Starts a generic wx_object server and invokes Mod:init(Args) in the %% new process. -doc """ -start(Name, Mod, Args, Options) -> wxWindow:wxWindow() | {error, term()} - Starts a generic wx_object server and invokes Mod:init(Args) in the new process. """. -spec start(Name, Mod, Args, Options) -> wxWindow:wxWindow() | {error, term()} when @@ -316,8 +312,6 @@ start(Name, Mod, Args, Options) -> %% @doc Starts a generic wx_object server and invokes Mod:init(Args) in the %% new process. -doc """ -start_link(Mod, Args, Options) -> wxWindow:wxWindow() | {error, term()} - Starts a generic wx_object server and invokes Mod:init(Args) in the new process. """. -spec start_link(Mod, Args, Options) -> wxWindow:wxWindow() | {error, term()} when @@ -334,8 +328,6 @@ start_link(Mod, Args, Options) -> %% @doc Starts a generic wx_object server and invokes Mod:init(Args) in the %% new process. -doc """ -start_link(Name, Mod, Args, Options) -> wxWindow:wxWindow() | {error, term()} - Starts a generic wx_object server and invokes Mod:init(Args) in the new process. """. -spec start_link(Name, Mod, Args, Options) -> wxWindow:wxWindow() | {error, term()} when @@ -360,8 +352,6 @@ gen_response(Reply) -> %% the process is terminated. If the process does not exist, an %% exception is raised. -doc """ -stop(Obj) -> ok - Stops a generic wx_object server with reason 'normal'. Invokes terminate(Reason,State) in the server. The call waits until the process is terminated. If the process does not exist, an exception is raised. @@ -386,8 +376,6 @@ stop(Name) when is_atom(Name) orelse is_pid(Name) -> %% the process is terminated. If the call times out, or if the process %% does not exist, an exception is raised. -doc """ -stop(Obj, Reason, Timeout) -> ok - Stops a generic wx_object server with the given Reason. Invokes terminate(Reason,State) in the server. The call waits until the process is terminated. If the call times out, or if the process does not exist, an @@ -414,8 +402,6 @@ stop(Name, Reason, Timeout) when is_atom(Name) orelse is_pid(Name) -> %% The call waits until it gets a result. %% Invokes handle_call(Request, From, State) in the server -doc """ -call(Obj, Request) -> term() - Make a call to a wx_object server. The call waits until it gets a result. Invokes handle_call(Request, From, State) in the server """. @@ -440,8 +426,6 @@ call(Name, Request) when is_atom(Name) orelse is_pid(Name) -> %% @doc Make a call to a wx_object server with a timeout. %% Invokes handle_call(Request, From, State) in server -doc """ -call(Obj, Request, Timeout) -> term() - Make a call to a wx_object server with a timeout. Invokes handle_call(Request, From, State) in server """. @@ -468,8 +452,6 @@ call(Name, Request, Timeout) when is_atom(Name) orelse is_pid(Name) -> %% and return a RequestId which can/should be used with wait_response/[1|2]. %% Invokes handle_call(Request, From, State) in server. -doc """ -send_request(Obj, Request::term()) -> request_id() - Make an send_request to a generic server. and return a RequestId which can/should be used with wait_response/\[1|2]. Invokes handle_call(Request, From, State) in server. @@ -483,9 +465,6 @@ send_request(Pid, Request) when is_atom(Pid) orelse is_pid(Pid) -> %% @doc Wait infinitely for a reply from a generic server. -doc """ -wait_response(RequestId::request_id()) -> {reply, Reply::term()} | {error, -{term(), server_ref()}} - Wait infinitely for a reply from a generic server. """. -spec wait_response(RequestId::request_id()) -> @@ -495,21 +474,15 @@ wait_response(RequestId) -> %% @doc Wait 'timeout' for a reply from a generic server. -doc """ -wait_response(Key::request_id(), Timeout::timeout()) -> {reply, Reply::term()} | -timeout | {error, {term(), server_ref()}} - Wait 'timeout' for a reply from a generic server. """. --spec wait_response(Key::request_id(), timeout()) -> +-spec wait_response(Key::request_id(), Timeout :: timeout()) -> {reply, Reply::term()} | 'timeout' | {error, {term(), server_ref()}}. wait_response(RequestId, Timeout) -> gen:wait_response(RequestId, Timeout). %% @doc Check if a received message was a reply to a RequestId -doc """ -check_response(Msg::term(), Key::request_id()) -> {reply, Reply::term()} | false -| {error, {term(), server_ref()}} - Check if a received message was a reply to a RequestId """. -spec check_response(Msg::term(), Key::request_id()) -> @@ -520,8 +493,6 @@ check_response(Msg, RequestId) -> %% @doc Make a cast to a wx_object server. %% Invokes handle_cast(Request, State) in the server -doc """ -cast(Obj, Request) -> ok - Make a cast to a wx_object server. Invokes handle_cast(Request, State) in the server """. @@ -537,8 +508,6 @@ cast(Name, Request) when is_atom(Name) orelse is_pid(Name) -> %% @doc Get the pid of the object handle. -doc """ -get_pid(Obj) -> pid() - Get the pid of the object handle. """. -spec get_pid(Obj) -> pid() when @@ -548,11 +517,9 @@ get_pid(#wx_ref{state=Pid}) when is_pid(Pid) -> %% @doc Sets the controlling process of the object handle. -doc """ -set_pid(Obj, Pid::pid()) -> wx:wx_object() - Sets the controlling process of the object handle. """. --spec set_pid(Obj, pid()) -> wx:wx_object() when +-spec set_pid(Obj, Pid :: pid()) -> wx:wx_object() when Obj::wx:wx_object()|atom()|pid(). set_pid(#wx_ref{}=R, Pid) when is_pid(Pid) -> R#wx_ref{state=Pid}. @@ -562,7 +529,7 @@ set_pid(#wx_ref{}=R, Pid) when is_pid(Pid) -> %% ----------------------------------------------------------------- %% @doc Get the pid of the object handle. -doc """ -reply(X1::{pid(), Tag::term()}, Reply::term()) -> pid() +reply(PidTag, Reply) Get the pid of the object handle. """. From 45b1fc1d6f71f85ac07d9c0341ab13232e6485c5 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Tue, 5 Nov 2024 12:58:25 +0100 Subject: [PATCH 12/17] ftp: Remove trailing anchors These anchors were used a long time ago to point to the function after the current function, but their use have become obsolete with the usage of ex_doc. --- lib/ftp/src/ftp.erl | 4 ---- 1 file changed, 4 deletions(-) diff --git a/lib/ftp/src/ftp.erl b/lib/ftp/src/ftp.erl index 00962b116c07..dfa70cbe992e 100644 --- a/lib/ftp/src/ftp.erl +++ b/lib/ftp/src/ftp.erl @@ -288,8 +288,6 @@ The available configuration options are as follows: in all other functions, and they are to be called by the process that created the connection. The FTP client process monitors the process that created it and terminates if that process terminates. - -[](){: #pwd } """. -spec open(Host :: string() | inet:ip_address(), Opts) -> {'ok', Client :: client()} | {'error', Reason :: term()} when @@ -320,8 +318,6 @@ open(Host, Port) -> -doc(#{title => <<"Connection API">>}). -doc """ Performs login of `User` with `Pass`. - -[](){: #user4 } """. -spec user(Pid :: pid(), User :: string(), From ba308e90dbfd35d5d3e3cad6835189ecd407f9cd Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Tue, 5 Nov 2024 12:58:35 +0100 Subject: [PATCH 13/17] inets: Remove trailing anchors These anchors were used a long time ago to point to the function after the current function, but their use have become obsolete with the usage of ex_doc. --- lib/inets/src/http_client/httpc.erl | 4 ---- lib/inets/src/http_server/httpd_socket.erl | 2 -- lib/inets/src/inets_app/inets.erl | 14 -------------- 3 files changed, 20 deletions(-) diff --git a/lib/inets/src/http_client/httpc.erl b/lib/inets/src/http_client/httpc.erl index ce9123d2e7a6..e03bfcf9b621 100644 --- a/lib/inets/src/http_client/httpc.erl +++ b/lib/inets/src/http_client/httpc.erl @@ -660,8 +660,6 @@ Sets options to be used for subsequent requests. > > The current implementation assumes the requests to the same host, port > combination will use the same socket options. - -[](){: #get_options } """. -doc(#{since => <<"OTP R13B04">>}). -spec set_options(Options, Profile) -> ok | {error, Reason} when @@ -1080,8 +1078,6 @@ reset_cookies(Profile) -> -doc """ Triggers the next message to be streamed, that is, the same behavior as active ones for sockets. - -[](){: #verify_cookies } [](){: #store_cookies } """. -doc(#{since => <<"OTP R13B04">>}). -spec stream_next(Pid) -> ok when diff --git a/lib/inets/src/http_server/httpd_socket.erl b/lib/inets/src/http_server/httpd_socket.erl index ade7c3b75f69..9e423d9dce28 100644 --- a/lib/inets/src/http_server/httpd_socket.erl +++ b/lib/inets/src/http_server/httpd_socket.erl @@ -44,8 +44,6 @@ mechanism is transparently used, that is, `ip_comm` or `ssl`. `deliver/3` sends `Data` over `Socket` using the specified `SocketType`. `Socket` and `SocketType` is to be the socket and the `socket_type` form the `mod` record as defined in `httpd.hrl` - -[](){: #peername } """. -spec deliver(SocketType, Socket, Data) -> Result when SocketType :: httpd:socket_type(), diff --git a/lib/inets/src/inets_app/inets.erl b/lib/inets/src/inets_app/inets.erl index 457831bbd7dd..9d051cef0fb8 100644 --- a/lib/inets/src/inets_app/inets.erl +++ b/lib/inets/src/inets_app/inets.erl @@ -77,8 +77,6 @@ start() -> -doc """ Starts the `Inets` application. Default type is `temporary`. See also `m:application`. - -[](){: #stop } """. -spec start(Type) -> ok | {error, Reason} when Type :: application:restart_type(), @@ -146,8 +144,6 @@ started. > #### Warning {: .warning } > The stand_alone option is considered deprecated. > - -[](){: #stop2 } """. -spec start(Service, ServiceConfig, How) -> Result when Service :: inets_service(), @@ -169,8 +165,6 @@ start(Service, ServiceConfig, How) -> %%-------------------------------------------------------------------- -doc """ Stops the `Inets` application. See also `m:application`. - -[](){: #start2 } """. -spec stop() -> ok. stop() -> @@ -189,8 +183,6 @@ stop() -> Stops a started service of the `Inets` application or takes down a `stand_alone`\-service gracefully. When option `stand_alone` is used in start, only the pid is a valid argument to stop. - -[](){: #see_also } """. -spec stop(Service, Reference) -> ok | {error, Reason} when Service :: inets_service() | stand_alone, @@ -216,8 +208,6 @@ Returns a list of currently running services. > #### Note {: .info } > > Services started as `stand_alone` are not listed. - -[](){: #services_info } """. -spec services() -> [{inets_service(), pid()}] | {error, inets_not_started}. services() -> @@ -244,8 +234,6 @@ an `[{Option, Value}]` list. The information in the list is specific for each service and each service has probably its own info function that gives more details about the service. If specific service info returns `{error, Reason}`, Info will contain Reason term. - -[](){: #service_names } """. -spec services_info() -> [service_info()] | {error, inets_not_started}. @@ -477,8 +465,6 @@ key1search(Key, Vals, Def) -> %%------------------------------------------------------------------- -doc """ Returns a list of available service names. - -[](){: #start } """. -spec service_names() -> [inets_service()]. service_names() -> From 57da6ec0e4b6d909a7fd953410be3480656c7305 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Tue, 5 Nov 2024 12:58:46 +0100 Subject: [PATCH 14/17] megaco: Remove trailing anchors These anchors were used a long time ago to point to the function after the current function, but their use have become obsolete with the usage of ex_doc. --- lib/megaco/doc/guides/megaco_debug.md | 4 +- lib/megaco/doc/guides/megaco_encode.md | 6 +- lib/megaco/doc/guides/megaco_mib.md | 2 +- lib/megaco/doc/guides/megaco_run.md | 26 ++--- lib/megaco/src/app/megaco.erl | 129 +++++---------------- lib/megaco/src/engine/megaco_encoder.erl | 8 +- lib/megaco/src/engine/megaco_transport.erl | 21 ++-- lib/megaco/src/engine/megaco_user.erl | 77 +++++------- 8 files changed, 92 insertions(+), 181 deletions(-) diff --git a/lib/megaco/doc/guides/megaco_debug.md b/lib/megaco/doc/guides/megaco_debug.md index 9aaeda6022cd..02ad95c7bc47 100644 --- a/lib/megaco/doc/guides/megaco_debug.md +++ b/lib/megaco/doc/guides/megaco_debug.md @@ -31,8 +31,8 @@ given external function. Event traces can be viewed in a generic message sequence chart tool, `et`, or as standard output (events are written to stdio). -See [enable_trace](`m:megaco#enable_trace`), -[disable_trace](`m:megaco#disable_trace`) and [set_trace](`m:megaco#set_trace`) +See [enable_trace](`megaco:enable_trace/2`), +[disable_trace](`megaco:disable_trace/0`) and [set_trace](`megaco:set_trace/1`) for more info. ## Measurement and transformation diff --git a/lib/megaco/doc/guides/megaco_encode.md b/lib/megaco/doc/guides/megaco_encode.md index 91767aba5720..e02e3918f0a7 100644 --- a/lib/megaco/doc/guides/megaco_encode.md +++ b/lib/megaco/doc/guides/megaco_encode.md @@ -222,7 +222,7 @@ are two ways to get this working: - Add the `{scanner, flex}` (or similar) directive to an Erlang system config file for the megaco app (see [initial configuration](megaco_run.md#initial_config) chapter for details). - - Retrieve the encoding-config using the [system_info](`m:megaco#system_info`) + - Retrieve the encoding-config using the [system_info](`megaco:system_info/1`) function (with `Item = text_config`). - Update the receive handle with the encoding-config (the `encoding_config` field). @@ -296,8 +296,8 @@ For outgoing messages: - Update the connection info protocol_version. - Override protocol version when sending a message by adding the item - `{protocol_version, integer()}` to the Options. See [call](`m:megaco#call`) or - [cast](`m:megaco#cast`). + `{protocol_version, integer()}` to the Options. See [call](`megaco:call/3`) or + [cast](`megaco:cast/3`). Note that this does not effect the messages that are sent autonomously by the stack. They use the protocol_version of the connection info. diff --git a/lib/megaco/doc/guides/megaco_mib.md b/lib/megaco/doc/guides/megaco_mib.md index 6e4d0a0601fd..6785cc6a1cd3 100644 --- a/lib/megaco/doc/guides/megaco_mib.md +++ b/lib/megaco/doc/guides/megaco_mib.md @@ -35,7 +35,7 @@ The implementation of the statistic counters is lightweight. I.e. the statistic counters are handled separately by different entities of the application. For instance our two transport module(s) (see [megaco_tcp](`megaco_tcp:get_stats/0`) and [megaco_udp](`megaco_udp:get_stats/0`)) maintain their own counters and the -application engine (see [megaco](`m:megaco#stats`)) maintain its own counters. +application engine (see [megaco](`megaco:get_stats/2`)) maintain its own counters. This also means that if a user implement their own transport service then it has to maintain its own statistics. diff --git a/lib/megaco/doc/guides/megaco_run.md b/lib/megaco/doc/guides/megaco_run.md index d9b9e7dfcb64..306f1bd2983b 100644 --- a/lib/megaco/doc/guides/megaco_run.md +++ b/lib/megaco/doc/guides/megaco_run.md @@ -149,17 +149,17 @@ There are three kinds of configuration: A User is an entity identified by a MID, e.g. a MGC or a MG. This information can be retrieved using - [megaco:user_info](`m:megaco#user_info`). + [megaco:user_info](`megaco:user_info/2`). - Connection info - Information regarding connections. Read/Write. This information can be retrieved using - [megaco:conn_info](`m:megaco#conn_info`). + [megaco:conn_info](`megaco:conn_info/2`). - System info - System wide information. Read only. This information can be retrieved using - [megaco:system_info](`m:megaco#system_info`). + [megaco:system_info](`megaco:system_info/1`). [](){: #initial_config } @@ -190,8 +190,8 @@ more info. ## Changing the configuration The configuration can be changed during runtime. This is done with the functions -[megaco:update_user_info](`m:megaco#update_user_info`) and -[megaco:update_conn_info](`m:megaco#update_conn_info`) +[megaco:update_user_info](`megaco:update_user_info/3`) and +[megaco:update_conn_info](`megaco:update_conn_info/3`) [](){: #transaction_sender } @@ -199,8 +199,8 @@ The configuration can be changed during runtime. This is done with the functions The transaction sender is a process (one per connection), which handle all transaction sending, if so configured (see -[megaco:user_info](`m:megaco#user_info`) and -[megaco:conn_info](`m:megaco#conn_info`)). +[megaco:user_info](`megaco:user_info/2`) and +[megaco:conn_info](`megaco:conn_info/2`)). The purpose of the transaction sender is to accumulate transactions for a more efficient message sending. The transactions that are accumulated are transaction @@ -248,25 +248,25 @@ check this. Instead, it is up to the user to configure this properly. This is handled automatically by the megaco application. There is however one thing that need to be configured by the user, the - [segment_recv_timer](`m:megaco#user_info`) option. + [segment_recv_timer](`megaco:user_info/2`) option. Note that the segments are delivered to the user differently depending on which function is used to issue the original request. When issuing the request - using the [megaco:cast](`m:megaco#cast`) function, the segments are delivered - to the user via the [handle_trans_reply](`m:megaco_user#trans_reply`) callback + using the [megaco:cast](`megaco:cast/3`) function, the segments are delivered + to the user via the [handle_trans_reply](`c:megaco_user:handle_trans_reply/5`) callback function one at a time, as they arrive. But this obviously doe not work for - the [megaco:call](`m:megaco#call`) function. In this case, the segments are + the [megaco:call](`megaco:call/3`) function. In this case, the segments are accumulated and then delivered all at once as the function returns. - Sending segmented messages: This is also handled automatically by the megaco application. First of all, segmentation is only attempted if so configured, see the - [segment_send](`m:megaco#user_info`) option. Secondly, megaco relies on the + [segment_send](`megaco:user_info/2`) option. Secondly, megaco relies on the ability of the used codec to encode action replies, which is the smallest component the megaco application handles when segmenting. Thirdly, the reply will be segmented only if the sum of the size of the action replies (plus an arbitrary message header size) are greater then the specified max message size - (see the [max_pdu_size](`m:megaco#user_info`) option). Finally, if + (see the [max_pdu_size](`megaco:user_info/2`) option). Finally, if segmentation is decided, then each action reply will make up its own (segment) message. diff --git a/lib/megaco/src/app/megaco.erl b/lib/megaco/src/app/megaco.erl index ca741e091334..0d91fc4fcb95 100644 --- a/lib/megaco/src/app/megaco.erl +++ b/lib/megaco/src/app/megaco.erl @@ -246,14 +246,14 @@ corresponding value can be of any type.[](){: #ci_control_pid } request-keep-alive timer. This timer is started when the _first_ reply to an asynchronous request - (issued using the [megaco:cast/3](`m:megaco#cast`) function) arrives. As long + (issued using the `megaco:cast/3` function) arrives. As long as this timer is running, replies will be delivered via the - [handle_trans_reply/4,5](`m:megaco_user#trans_reply`) callback function, with + [handle_trans_reply/4,5](`c:megaco_user:handle_trans_reply/5`) callback function, with their "arrival number" (see `UserReply` of the - [handle_trans_reply/4,5](`m:megaco_user#trans_reply`) callback function). + [handle_trans_reply/4,5](`c:megaco_user:handle_trans_reply/5`) callback function). Replies arriving after the timer has expired, will be delivered using the - [handle_unexpected_trans/3,4](`m:megaco_user#unexpected_trans`) callback + [handle_unexpected_trans/3,4](`c:megaco_user:handle_unexpected_trans/4`) callback function. Value type: `plain` | [non_neg_integer()](`t:erlang:non_neg_integer/0`) @@ -301,11 +301,11 @@ corresponding value can be of any type.[](){: #ci_control_pid } - **`call_proxy_gc_timeout`** - Timeout time for the call proxy. - When a request is sent using the [call/3](`m:megaco#call`) function, a proxy + When a request is sent using the `call/3` function, a proxy process is started to handle all replies. When the reply has been received and delivered to the user, the proxy process continue to exist for as long as this option specifies. Any received messages, is passed on to the user via the - [handle_unexpected_trans](`m:megaco_user#handle_unexpected_trans`) callback + [handle_unexpected_trans](`c:megaco_user:handle_unexpected_trans/4`) callback function. The timeout time is in milliseconds. A value of 0 (zero) means that the proxy @@ -429,7 +429,7 @@ corresponding value can be of any type.[](){: #ci_control_pid } package). This parameter specifies how many pending messages that can be sent (for a given received transaction request). When the limit is exceeded, the transaction is aborted (see - [handle_trans_request_abort](`m:megaco_user#request_abort`)) and an error + [handle_trans_request_abort](`c:megaco_user:handle_trans_request_abort/5`)) and an error message is sent to the other side. Note that this has no effect on the actual sending of pending transactions. @@ -546,7 +546,7 @@ corresponding value can be of any type.[](){: #ci_control_pid } - **`segment_reply_ind`** - This option specifies if the user shall be notified of received segment replies or not. - See [handle_segment_reply](`m:megaco_user#segment_reply`) callback function + See [handle_segment_reply](`c:megaco_user:handle_segment_reply/6`) callback function for more information. Value type: [boolean()](`t:erlang:boolean/0`) @@ -562,8 +562,8 @@ corresponding value can be of any type.[](){: #ci_control_pid } When the timer finally expires, a "megaco segments not received" (459) error message is sent to the other side and the user is notified with a `segment timeout` `UserReply` in either the - [handle_trans_reply](`m:megaco_user#trans_reply`) callback function or the - return value of the [call](`m:megaco#call`) function. + [handle_trans_reply](`c:megaco_user:handle_trans_reply/5`) callback function or the + return value of the `call/2` function. Value type: `t:megaco_timer/0` @@ -749,14 +749,14 @@ corresponding value can be of any type.[](){: #ci_control_pid } request-keep-alive timer. This timer is started when the _first_ reply to an asynchronous request - (issued using the [megaco:cast/3](`m:megaco#cast`) function) arrives. As long + (issued using the `megaco:cast/3` function) arrives. As long as this timer is running, replies will be delivered via the - [handle_trans_reply/4,5](`m:megaco_user#trans_reply`) callback function, with + [handle_trans_reply/4,5](`c:megaco_user:handle_trans_reply/5`) callback function, with their "arrival number" (see `UserReply` of the - [handle_trans_reply/4,5](`m:megaco_user#trans_reply`) callback function). + [handle_trans_reply/4,5](`c:megaco_user:handle_trans_reply/5`) callback function). Replies arriving after the timer has expired, will be delivered using the - [handle_unexpected_trans/3,4](`m:megaco_user#unexpected_trans`) callback + [handle_unexpected_trans/3,4](`c:megaco_user:handle_unexpected_trans/4`) callback function. Value type: `plain` | [non_neg_integer()](`t:erlang:non_neg_integer/0`) @@ -767,11 +767,11 @@ corresponding value can be of any type.[](){: #ci_control_pid } - **`call_proxy_gc_timeout`** - Timeout time for the call proxy. - When a request is sent using the [call/3](`m:megaco#call`) function, a proxy + When a request is sent using the `call/3` function, a proxy process is started to handle all replies. When the reply has been received and delivered to the user, the proxy process continue to exist for as long as this option specifies. Any received messages, is passed on to the user via the - [handle_unexpected_trans](`m:megaco_user#handle_unexpected_trans`) callback + [handle_unexpected_trans](`c:megaco_user:handle_unexpected_trans/4`) callback function. The timeout time is in milliseconds. A value of 0 (zero) means that the proxy @@ -897,7 +897,7 @@ corresponding value can be of any type.[](){: #ci_control_pid } package). This parameter specifies how many pending messages that can be sent (for a given received transaction request). When the limit is exceeded, the transaction is aborted (see - [handle_trans_request_abort](`m:megaco_user#request_abort`)) and an error + [handle_trans_request_abort](`c:megaco_user:handle_trans_request_abort/5`)) and an error message is sent to the other side. Note that this has no effect on the actual sending of pending transactions. @@ -1030,7 +1030,7 @@ corresponding value can be of any type.[](){: #ci_control_pid } - **`segment_reply_ind`** - This option specifies if the user shall be notified of received segment replies or not. - See [handle_segment_reply](`m:megaco_user#segment_reply`) callback function + See [handle_segment_reply](`c:megaco_user:handle_segment_reply/6`) callback function for more information. Value type: [boolean()](`t:erlang:boolean/0`) @@ -1046,8 +1046,8 @@ corresponding value can be of any type.[](){: #ci_control_pid } When the timer finally expires, a "megaco segments not received" (459) error message is sent to the other side and the user is notified with a `segment timeout` `UserReply` in either the - [handle_trans_reply](`m:megaco_user#trans_reply`) callback function or the - return value of the [call](`m:megaco#call`) function. + [handle_trans_reply](`c:megaco_user:handle_trans_reply/5`) callback function or the + return value of the `call/3` function. Value type: `t:megaco_timer/0` @@ -1220,7 +1220,6 @@ to file or to stdout after formating). Value type: [\{recv | sent, [\{`t:transaction_id/0`, [non_neg_integer()](`t:erlang:non_neg_integer/0`)\}]\}] -[](){: #start } """. -type system_info_item() :: text_config | connections | @@ -1247,7 +1246,6 @@ statically configured by setting the application environment variable 'users' to a list of \{UserMid, Config\} tuples. See the function megaco:start_user/2 for details. -[](){: #stop } """. -spec start() -> ok | {error, Reason} when Reason :: term(). @@ -1263,7 +1261,6 @@ start() -> -doc """ Stops the Megaco application -[](){: #start_user } """. -spec stop() -> ok | {error, Reason} when Reason :: term(). @@ -1287,7 +1284,6 @@ A user is identified by its UserMid, which must be a legal Megaco MID. Config is a list of \{Item, Value\} tuples. See megaco:user_info/2 about which items and values that are valid. -[](){: #stop_user } """. -spec start_user(UserMid, Config) -> ok | {error, Reason} when UserMid :: mid(), @@ -1309,7 +1305,6 @@ Delete the configuration of a user Requires that the user does not have any active connection. -[](){: #user_info } [](){: #user_info_11 } [](){: #user_info_23 } """. -spec stop_user(UserMid) -> ok | {error, Reason} when UserMid :: mid(), @@ -1344,7 +1339,6 @@ Lookup user information about currently active requests. Lookup user information about currently active replies. -[](){: #update_user_info } """. -spec user_info(UserMid, requests) -> [{Conn, [TransId]}] when UserMid :: mid(), @@ -1381,7 +1375,6 @@ Update information about a user Requires that the user is started. -[](){: #conn_info } [](){: #conn_info_11 } [](){: #conn_info_24 } """. -spec update_user_info(UserMid, Item, Value) -> ok | {error, Reason} when UserMid :: mid(), @@ -1415,31 +1408,6 @@ Requires that the connection is active. Failure: `exit` if, for instance, `ConnHandle` refers to a connection that no longer exists. - -[](){: #conn_info_21 } - -Lookup all connection information about an _active_ connection - -See [conn_info](`m:megaco#conn_info_24`) for more info. - -Failure: `exit` if, for instance, `ConnHandle` refers to a connection that no -longer exists. - -[](){: #conn_info_22 } - -Lookup information about currently active requests for an _active_ connection - -Failure: `exit` if, for instance, `ConnHandle` refers to a connection that no -longer exists. - -[](){: #conn_info_23 } - -Lookup information about currently active replies for an _active_ connection - -Failure: `exit` if, for instance, `ConnHandle` refers to a connection that no -longer exists. - -[](){: #update_conn_info } """. -spec conn_info(ConnHandle, all) -> [{Item, Value}] when ConnHandle :: conn_handle(), @@ -1485,7 +1453,6 @@ Update information about an active connection Requires that the connection is activated. See `t:conn_info_item/0` about which items and values that are valid. -[](){: #system_info } """. -spec update_conn_info(ConnHandle, Item, Value) -> ok | {error, Reason} when ConnHandle :: conn_handle(), @@ -1506,11 +1473,8 @@ This function produces a list of information about the megaco application. Such as users and their config, connections and their config, statistics and so on. This information can be produced by the functions -[user_info](`m:megaco#user_info`), [conn_info](`m:megaco#conn_info`), -[system_info](`m:megaco#system_info`) and [get_stats](`m:megaco#get_stats`) but +`user_info/2`, `conn_info/2`, `system_info/1` and `get_stats/2` but this is a simple way to get it all at once. - -[](){: #connect } """. -spec info() -> Info when Info :: [{Key, Value}], @@ -1591,7 +1555,6 @@ system_info() -> -doc """ Lookup system information. -[](){: #info } """. -spec system_info(Item) -> Value when Item :: system_info_item(), @@ -1684,7 +1647,7 @@ megaco_udp. Read the documentation about each transport module about the details. The connect is done in two steps: first an internal `connection setup` and then -by calling the user [handle_connect](`m:megaco_user#connect`) callback function. +by calling the user [handle_connect](`c:megaco_user:handle_connect/3`) callback function. The first step could result in an error with `Reason = ConnectReason` and the second an error with `Reason = HandleConnectReason`: @@ -1692,14 +1655,13 @@ second an error with `Reason = HandleConnectReason`: application itself. - **`HandleConnectReason`** - An error with this reason is caused by the user - [handle_connect](`m:megaco_user#connect`) callback function either returning + [handle_connect](`c:megaco_user:handle_connect/3`) callback function either returning an error or an invalid value. `Extra` can be any `t:term/0` except the atom `ignore_extra`. It is passed (back) to the user via the callback function -[handle_connect/3](`m:megaco_user#connect`). +[handle_connect/3](`c:megaco_user:handle_connect/3`). -[](){: #disconnect } """. -spec connect(ReceiveHandle, RemoteMid, SendHandle, ControlPid, Extra) -> {ok, ConnHandle} | {error, Reason} when @@ -1733,7 +1695,6 @@ Tear down a "virtual" connection Causes the `UserMod:handle_disconnect/2` callback function to be invoked. See the megaco_user module for more info about the callback arguments. -[](){: #call } """. -spec disconnect(ConnHandle, DiscoReason) -> ok | {error, ErrReason} when ConnHandle :: conn_handle(), @@ -1779,7 +1740,7 @@ transactionError. A `UserCancelReason`, indicates that the request has been canceled by the user. `ReasonForUserCancel` is the reason given in the call to the -[cancel](`m:megaco#cancel`) function. +`cancel/2` function. A send error (`SendReason`), indicates that the send function of the megaco transport callback module failed to send the request. There are two separate @@ -1794,7 +1755,6 @@ For more info about the 'extra' part of the result (`SuccessExtra` and `ErrorExtra`), see the [note](`m:megaco_user#extra_argument`) in the user callback module documentation. -[](){: #cast } """. -spec call(ConnHandle, ActionRequests, SendOptions) -> {ProtocolVersion, UserReply | [UserReply]} when @@ -1869,7 +1829,6 @@ about the callback arguments. Given as `ReplyData` argument to UserMod:handle_trans_reply/4. -[](){: #encode_actions } """. -spec cast(ConnHandle, ActionRequests, SendOptions) -> ok | {error, Reason} when @@ -1899,13 +1858,12 @@ cast(ConnHandle, ActionRequests, Options) -> Tests if the Actions argument is correctly composed. This function is only intended for testing purposes. It's supposed to have a -same kind of interface as the [call](`m:megaco#call`) or [cast](`m:megaco#cast`) +same kind of interface as the `call/3` or `cast/3` functions (with the additions of the `EncodingMod` and `EncodingConfig` arguments). It composes a complete megaco message end attempts to encode it. The return value, will be a tuple of the composed megaco message and the encode result. -[](){: #test_reply } """. -spec test_request(ConnHandle, Version, EncodingMod, EncodingConfig, @@ -1935,8 +1893,8 @@ Tests if the Reply argument is correctly composed. This function is only intended for testing purposes. It's supposed to test the `actual_reply()` return value of the callback functions -[handle_trans_request](`m:megaco_user#trans_request`) and -[handle_trans_long_request](`m:megaco_user#trans_long_request`) functions (with +[handle_trans_request](`c:megaco_user:handle_trans_request/4`) and +[handle_trans_long_request](`c:megaco_user:handle_trans_long_request/4`) functions (with the additions of the `EncodingMod` and `EncodingConfig` arguments). It composes a complete megaco message end attempts to encode it. The return value, will be a tuple of the composed megaco message and the encode result. @@ -1972,7 +1930,6 @@ The global counters handle events that cannot be attributed to a single connection (e.g. protocol errors that occur before the connection has been properly setup). -[](){: #get_stats_1_1 } """. -spec get_stats() -> {ok, [TotalStats]} | {error, Reason} when TotalStats :: {conn_handle(), [Stats]} | @@ -1996,7 +1953,6 @@ properly setup). Retreive all (SNMP) statistic counters maintained by the megaco application, for a specific connection. -[](){: #get_stats_2 } """. -spec get_stats(GCounter) -> {ok, Value} | {error, Reason} when GCounter :: global_counter(), @@ -2013,7 +1969,6 @@ get_stats(ConnHandleOrGCounter) -> -doc """ Retreive a (SNMP) statistic counter maintained by the megaco application. -[](){: #reset_stats } [](){: #reset_stats_0 } """. -spec get_stats(ConnHandle, Counter) -> {ok, Value} | {error, Reason} when ConnHandle :: conn_handle(), @@ -2033,7 +1988,6 @@ get_stats(ConnHandle, Counter) -> -doc """ Reset all (SNMP) statistics counters. -[](){: #reset_stats_1_1 } """. -spec reset_stats() -> void(). @@ -2047,7 +2001,6 @@ Reset the specified (SNMP) statistics counter. Reset all (SNMP) statistics counters for a connection. -[](){: #test_request } """. -spec reset_stats(GCounter) -> void() when GCounter :: global_counter(); @@ -2069,7 +2022,6 @@ This causes outstanding megaco:call/3 requests to return. The callback functions UserMod:handle_reply/4 and UserMod:handle_trans_ack/4 are also invoked where it applies. See the megaco_user module for more info about the callback arguments. -[](){: #process_received_message } """. -spec cancel(ConnHandle, CancelReason) -> ok | {error, Reason} when ConnHandle :: conn_handle(), @@ -2112,7 +2064,7 @@ arguments. The argument `Extra` is just an opaque data structure passed to the user via the callback functions in the [user callback module](`m:megaco_user`). Note however that if `Extra` has the value `extra_undefined` the argument will be ignored -(same as if [`process_received_message/4`](`process_received_message/4`) had +(same as if `process_received_message/4` had been called). See the documentation for the behaviour of the callback module, `m:megaco_user`, for more info. @@ -2158,7 +2110,6 @@ important the following callback function will be invoked: See the megaco_user module for more info about the callback arguments. -[](){: #receive_message } """. -spec process_received_message(ReceiveHandle, ControlPid, SendHandle, BinMsg, Extra) -> @@ -2195,13 +2146,8 @@ This is a callback function intended to be invoked by some transport modules when get an incoming message. Which transport that actually is used is up to the user to choose. -In principle, this function calls the `process_received_message/4,5` function -via a `spawn` to perform the actual processing. - -For further information see the -[process_received_message/4,5](`m:megaco#process_received_message`) function. - -[](){: #parse_digit_map } +In principle, this function calls the [process_received_message/4,5](`process_received_message/5`) +function via a `spawn` to perform the actual processing. """. -spec receive_message(ReceiveHandle, ControlPid, SendHandle, BinMsg, Extra) -> ok when @@ -2229,7 +2175,6 @@ When encoding action requests for one transaction, `Actions` should be `Actions` should be `[action_reqs()]`. Each element of the list is part of one transaction. -[](){: #token_tag2string } """. -spec encode_actions(ConnHandle, ActionRequests, Options) -> {ok, Result} | {error, Reason} when @@ -2284,7 +2229,6 @@ If no or an unknown version is given, the _best_ version is used (which is v3). If no match is found for `Tag`, `Result` will be the empty string (`[]`). -[](){: #cancel } """. -spec token_tag2string(Tag, EncodingMod, Version) -> Result when Tag :: atom(), @@ -2311,7 +2255,6 @@ Parses a digit map body Parses a digit map body, represented as a list of characters, into a list of state transitions suited to be evaluated by megaco:eval_digit_map/1,2. -[](){: #eval_digit_map } """. -spec parse_digit_map(DigitMapBody) -> {ok, ParsedDigitMap} | {error, Reason} when @@ -2355,7 +2298,6 @@ event is received when the digit map evaluator is expecting some other event). The unexpected events may either be ignored or rejected. The latter means that the evaluation is aborted and an error is returned. -[](){: #report_digit_event } """. -spec eval_digit_map(DigitMap, Timers) -> {ok, MatchResult} | {error, Reason} when @@ -2390,7 +2332,6 @@ process that is executing megaco:eval_digit_map/1,2. Note that the events `$s | $S`, `l | $L` and `$z | $Z` has nothing to do with the timers using the same characters. -[](){: #test_digit_event } """. -spec report_digit_event(DigitMapEvalPid, Events) -> ok | {error, Reason} when DigitMapEvalPid :: pid(), @@ -2412,7 +2353,6 @@ This function starts the evaluation of a digit map with megaco:eval_digit_map/1 and sends a sequence of events to it with megaco:report_digit_event/2 in order to simplify testing of digit maps. -[](){: #encode_sdp } """. -spec test_digit_event(DigitMap, Events) -> {ok, Kind, Letters} | {error, Reason} when @@ -2477,7 +2417,6 @@ This function performs the following transformation: - sdp_property_group() -> property_group() - sdp_property_groups() -> property_groups() -[](){: #decode_sdp } """. -spec encode_sdp(SDP) -> {ok, PP} | {error, Reason} when SDP :: sdp_property_parm() | @@ -2518,7 +2457,6 @@ This function performs the following transformation: - property_group() -> sdp_property_group() - property_groups() -> sdp_property_groups() -[](){: #versions } [](){: #versions1 } [](){: #versions2 } """. -spec decode_sdp(PP) -> {ok, SDP} | {error, Reason} when PP :: property_parm() | @@ -2574,7 +2512,6 @@ Example: {ok, V} = megaco:versions1(), megaco:format_versions(V). ``` -[](){: #enable_trace } """. -spec print_version_info(Versions) -> void() when Versions :: [VersionInfo], @@ -2750,7 +2687,6 @@ The difference between the two functions is in how they get the modules to check. `versions1` uses the app-file and `versions2` uses the function `application:get_key`. -[](){: #print_version_info } """. -spec versions2() -> {ok, VersionInfo} | {error, Reason} when VersionInfo :: list(), @@ -2959,7 +2895,6 @@ be printed on stdout using plain `io:format/2`. See `dbg` for further information. -[](){: #disable_trace } """. -spec enable_trace(Level, Destination) -> void() when Level :: trace_level(), @@ -3001,7 +2936,6 @@ enable_trace(Level, {Fun, _Data} = HandleSpec) when is_function(Fun) -> -doc """ This function is used to stop megaco tracing. -[](){: #set_trace } """. -spec disable_trace() -> void(). @@ -3028,7 +2962,6 @@ This function is used to change the megaco trace level. It is assumed that tracing has already been enabled (see `enable_trace` above). -[](){: #stats } [](){: #get_stats } [](){: #get_stats_0 } """. -spec set_trace(Level) -> void() when Level :: trace_level(). diff --git a/lib/megaco/src/engine/megaco_encoder.erl b/lib/megaco/src/engine/megaco_encoder.erl index 75db093eb304..e80beb050b7a 100644 --- a/lib/megaco/src/engine/megaco_encoder.erl +++ b/lib/megaco/src/engine/megaco_encoder.erl @@ -60,7 +60,6 @@ command_request() = #'CommandRequest'{} error_desc() = #'ErrorDescriptor'{} ``` -[](){: #encode_message } """. -export_type([ @@ -182,7 +181,6 @@ of the protocol we are using. As of version 3, it has two more fields. -doc """ Encode a megaco message. -[](){: #decode_message } """. -callback encode_message(EncodingConfig, Version, @@ -203,7 +201,6 @@ If on the other hand the Version argument is an integer, it means that this is the expected version of the message and the decoder for that version should be used. -[](){: #decode_mini_message } """. -callback decode_message(EncodingConfig, Version, @@ -225,7 +222,6 @@ initiated. This function is used by the megaco_messenger module when the Note again that a successfull decode only returns a partially initiated message. -[](){: #encode_transaction } """. -callback decode_mini_message(EncodingConfig, Version, @@ -244,7 +240,6 @@ This functionality is used both when the transaction sender is used and for segmentation. So, for either of those to work, this function _must_ be fully supported\! -[](){: #encode_action_requests } """. -callback encode_transaction(EncodingConfig, Version, @@ -257,11 +252,10 @@ supported\! -doc """ Encode megaco action requests. This function is called when the user calls the -function [encode_actions/3](`m:megaco#encode_actions`). If that function is +function [encode_actions/3](`megaco:encode_actions/3`). If that function is never used or if the codec cannot support this (the encoding of individual actions), then return with error reason `not_implemented`. -[](){: #encode_action_reply } """. -callback encode_action_requests(EncodingConfig, Version, diff --git a/lib/megaco/src/engine/megaco_transport.erl b/lib/megaco/src/engine/megaco_transport.erl index e21cb96d457a..fa086988a7ec 100644 --- a/lib/megaco/src/engine/megaco_transport.erl +++ b/lib/megaco/src/engine/megaco_transport.erl @@ -30,12 +30,10 @@ Megaco transport behaviour. The following functions should be exported from a `megaco_transport` callback module: -- [send_message/2](`m:megaco_transport#send_message`) [`mandatory`] -- [send_message/3](`m:megaco_transport#send_message`) [`optional`] -- [resend_message/2](`m:megaco_transport#resend_message`) [`optional`] -- +- `c:send_message/2` [`mandatory`] +- `c:send_message/3` [`optional`] +- `c:resend_message/2` [`optional`] -[](){: #send_message } """. -doc(#{equiv => send_message/3}). @@ -55,21 +53,20 @@ depends on what kind of message was sent. In the case of requests, megaco will cancel the message in much the same way as if `megaco:cancel` had been called (after a successfull send). The information will be propagated back to the user differently depending on how the request(s) -where issued: For requests issued using [megaco:call](`m:megaco#call`), the info +where issued: For requests issued using `megaco:call/3`, the info will be delivered in the return value. For requests issued using `megaco:cast` the info will be delivered via a call to the callback function -[handle_trans_reply](`m:megaco_user#trans_reply`). +[handle_trans_reply](`c:megaco_user:handle_trans_reply/5`). In the case of reply, megaco will cancel the reply and information of this will be returned to the user via a call to the callback function -[handle_trans_ack](`m:megaco_user#trans_ack`). +[handle_trans_ack](`c:megaco_user:handle_trans_ack/5`). The function [`send_message/3`](`c:send_message/3`) will only be called if the [resend_indication](`m:megaco#ui_resend_indication`) config option has been set to the value `flag`. The third argument, `Resend` then indicates if the message send is a resend or not. -[](){: #resend_message } """. -callback send_message(Handle, Msg, Resend) -> ok | {cancel, Reason :: term()} | Error when Handle :: term(), @@ -93,14 +90,14 @@ depends on what kind of message was sent. In the case of requests, megaco will cancel the message in much the same way as if `megaco:cancel` had been called (after a successfull send). The information will be propagated back to the user differently depending on how the request(s) -where issued: For requests issued using [megaco:call](`m:megaco#call`), the info +where issued: For requests issued using [megaco:call](`megaco:call/3`), the info will be delivered in the return value. For requests issued using `megaco:cast` the info will be delivered via a call to the callback function -[handle_trans_reply](`m:megaco_user#trans_reply`). +[handle_trans_reply](`c:megaco_user:handle_trans_reply/5`). In the case of reply, megaco will cancel the reply and information of this will be returned to the user via a call to the callback function -[handle_trans_ack](`m:megaco_user#trans_ack`). +[handle_trans_ack](`c:megaco_user:handle_trans_ack/5`). """. -callback resend_message(Handle, Msg) -> ok | {cancel, Reason :: term()} | Error when Handle :: term(), diff --git a/lib/megaco/src/engine/megaco_user.erl b/lib/megaco/src/engine/megaco_user.erl index 59e297cc01f5..f5ac59327ad1 100644 --- a/lib/megaco/src/engine/megaco_user.erl +++ b/lib/megaco/src/engine/megaco_user.erl @@ -40,17 +40,17 @@ Callback module for users of the Megaco application This module defines the callback behaviour of Megaco users. A megaco_user compliant callback module must export the following functions: -- [handle_connect/2,3](`m:megaco_user#connect`) -- [handle_disconnect/3](`m:megaco_user#disconnect`) -- [handle_syntax_error/3,4](`m:megaco_user#syntax_error`) -- [handle_message_error/3,4](`m:megaco_user#message_error`) -- [handle_trans_request/3,4](`m:megaco_user#trans_request`) -- [handle_trans_long_request/3,4](`m:megaco_user#trans_long_request`) -- [handle_trans_reply/4,5](`m:megaco_user#trans_reply`) -- [handle_trans_ack/4,5](`m:megaco_user#trans_ack`) -- [handle_unexpected_trans/3,4](`m:megaco_user#unexpected_trans`) -- [handle_trans_request_abort/4,5](`m:megaco_user#request_abort`) -- [handle_segment_reply/5,6](`m:megaco_user#segment_reply`) +- [handle_connect/2,3](`c:handle_connect/3`) +- [handle_disconnect/3](`c:handle_disconnect/3`) +- [handle_syntax_error/3,4](`c:handle_syntax_error/4`) +- [handle_message_error/3,4](`c:handle_message_error/4`) +- [handle_trans_request/3,4](`c:handle_trans_request/4`) +- [handle_trans_long_request/3,4](`c:handle_trans_long_request/4`) +- [handle_trans_reply/4,5](`c:handle_trans_reply/5`) +- [handle_trans_ack/4,5](`c:handle_trans_ack/5`) +- [handle_unexpected_trans/3,4](`c:handle_unexpected_trans/4`) +- [handle_trans_request_abort/4,5](`c:handle_trans_request_abort/5`) +- [handle_segment_reply/5,6](`c:handle_segment_reply/6`) The semantics of them and their exact signatures are explained below. @@ -58,8 +58,8 @@ The `user_args` configuration parameter which may be used to extend the argument list of the callback functions. For example, the handle_connect function takes by default two arguments: -```text - handle_connect(Handle, Version) +``` +handle_connect(Handle, Version) ``` but if the `user_args` parameter is set to a longer list, such as @@ -67,7 +67,7 @@ but if the `user_args` parameter is set to a longer list, such as this case two) extra arguments last in the argument list: ```erlang - handle_connect(Handle, Version, SomePid, SomeTableRef) +handle_connect(Handle, Version, SomePid, SomeTableRef) ``` [](){: #extra_argument } @@ -75,10 +75,10 @@ this case two) extra arguments last in the argument list: > #### Note {: .info } > > Must of the functions below has an optional `Extra` argument (e.g. -> [handle_unexpected_trans/4](`m:megaco_user#unexpected_trans`)). The functions +> [handle_unexpected_trans/4](`c:handle_unexpected_trans/4`)). The functions > which takes this argument will be called if and only if one of the functions -> [receive_message/5](`m:megaco#receive_message`) or -> [process_received_message/5](`m:megaco#process_received_message`) was called +> [`receive_message/5`](`megaco:receive_message/5`) or +> [`process_received_message/5`](`megaco:process_received_message/5`) was called > with the `Extra` argument different than `ignore_extra`. ## DATA TYPES @@ -114,7 +114,6 @@ connection configuration: - `megaco:conn_info(ConnHandle, protocol_version)`. -[](){: #connect } """. -export_type([ @@ -151,14 +150,12 @@ request (and send a message error reply to the gateway) by returning code 402 (unauthorized) and reason "Connection refused by user" (this is also the case for all unknown results, such as exit signals or throw). -See [note](`m:megaco_user#extra_argument`) above about the `Extra` argument in +See [note](#extra_argument) above about the `Extra` argument in [`handle_message_error/4`](`c:handle_message_error/4`). [`handle_connect/3`](`c:handle_connect/3`) (with `Extra`) can also be called as -a result of a call to the [megaco:connect/5](`m:megaco#connect`) function (if +a result of a call to the `megaco:connect/5` function (if that function is called with the `Extra` argument different than `ignore_extra`. - -[](){: #disconnect } """. -callback handle_connect(ConnHandle, ProtocolVersion, Extra) -> ok | error | {error, ErrorDescr} when @@ -172,8 +169,6 @@ Invoked when a connection is teared down The disconnect may either be made explicitly by a call to megaco:disconnect/2 or implicitly when the control process of the connection dies. - -[](){: #syntax_error } """. -callback handle_disconnect(ConnHandle, ProtocolVersion, Reason) -> megaco:void() when @@ -207,10 +202,9 @@ and `no_reply` respectively. Any other return values (including exit signals or throw) and the `DefaultED` will be used. -See [note](`m:megaco_user#extra_argument`) above about the `Extra` argument in +See [note](#extra_argument) above about the `Extra` argument in [`handle_syntax_error/4`](`c:handle_syntax_error/4`). -[](){: #message_error } """. -callback handle_syntax_error(ReceiveHandle, ProtocolVersion, DefaultED, Extra) -> reply | {reply, ED} | no_reply | {no_reply, ED} when @@ -239,10 +233,9 @@ probably don't want to reply to it, but it may indicate that you have outstanding transactions that not will get any response (request -> reply; reply -> ack). -See [note](`m:megaco_user#extra_argument`) above about the `Extra` argument in +See [note](#extra_argument) above about the `Extra` argument in [`handle_message_error/4`](`c:handle_message_error/4`). -[](){: #trans_request } """. -callback handle_message_error(ConnHandle, ProtocolVersion, ErrorDescr, Extra) -> megaco:void() when @@ -298,7 +291,7 @@ options: If for some reason megaco is unable to deliver the reply, the reason for this will be passed to the user via a call to the callback function - [handle_trans_ack](`m:megaco_user#trans_ack`), unless + [handle_trans_ack](`c:handle_trans_ack/5`), unless `ack_action() = discard_ack`. The ack_action() is either: @@ -331,10 +324,9 @@ Any other return values (including exit signals or throw) will result in an error descriptor with code 500 (internal gateway error) and the module name (of the callback module) as reason. -See [note](`m:megaco_user#extra_argument`) above about the `Extra` argument in +See [note](#extra_argument) above about the `Extra` argument in [`handle_trans_request/4`](`c:handle_trans_request/4`). -[](){: #trans_long_request } """. -callback handle_trans_request(ConnHandle, ProtocolVersion, @@ -394,10 +386,9 @@ Any other return values (including exit signals or throw) will result in an error descriptor with code 500 (internal gateway error) and the module name (of the callback module) as reason. -See [note](`m:megaco_user#extra_argument`) above about the `Extra` argument in +See [note](#extra_argument) above about the `Extra` argument in [`handle_trans_long_request/4`](`c:handle_trans_long_request/4`). -[](){: #trans_reply } """. -callback handle_trans_long_request(ConnHandle, ProtocolVersion, ReqData, Extra) -> Reply when @@ -494,7 +485,7 @@ following: the reply was segmented. - A `user_cancel_reason()`, indicates that the request has been canceled by the user. `reason_for_user_cancel()` is the reason given in the call to the - [cancel](`m:megaco#cancel`) function. + [cancel](`megaco:cancel/2`) function. - A `send_reason()`, indicates that the transport module [send_message](`c:megaco_transport:send_message/3`) function did not send the message. The reason for this can be: @@ -513,10 +504,9 @@ following: - `exceeded_recv_pending_limit` \- the pending limit was exceeded for this request. -See [note](`m:megaco_user#extra_argument`) above about the `Extra` argument in +See [note](#extra_argument) above about the `Extra` argument in [`handle_trans_reply/5`](`c:handle_trans_reply/5`). -[](){: #trans_ack } """. -callback handle_trans_reply(ConnHandle, ProtocolVersion, @@ -604,14 +594,13 @@ happens when: - **`reply_timer`** - The `reply_timer` eventually times out. - **reply send failure** - When megaco fails to send the reply (see - [handle_trans_reply](`m:megaco_user#trans_reply`)), for whatever reason. + [handle_trans_reply](`c:handle_trans_reply/5`)), for whatever reason. - **cancel** - The user has explicitly cancelled the wait (megaco:cancel/2). -See [note](`m:megaco_user#extra_argument`) above about the `Extra` argument in +See [note](#extra_argument) above about the `Extra` argument in [`handle_trans_ack/5`](`c:handle_trans_ack/5`). -[](){: #unexpected_trans } [](){: #handle_unexpected_trans } """. -callback handle_trans_ack(ConnHandle, ProtocolVersion, @@ -651,10 +640,9 @@ been done the app has no way of knowing where to send this message. The message is delivered to the "user" by calling this function on the local node (the node which has the link). -See [note](`m:megaco_user#extra_argument`) above about the `Extra` argument in +See [note](#extra_argument) above about the `Extra` argument in [`handle_unexpected_trans/4`](`c:handle_unexpected_trans/4`). -[](){: #request_abort } """. -callback handle_unexpected_trans(ConnHandle, ProtocolVersion, Trans, Extra) -> ok when @@ -681,10 +669,9 @@ Invoked when a transaction request has been aborted This function is invoked if the originating pending limit has been exceeded. This usually means that a request has taken abnormally long time to complete. -See [note](`m:megaco_user#extra_argument`) above about the `Extra` argument in +See [note](#extra_argument) above about the `Extra` argument in [`handle_trans_request_abort/5`](`c:handle_trans_request_abort/5`). -[](){: #segment_reply } """. -callback handle_trans_request_abort(ConnHandle, ProtocolVersion, @@ -712,11 +699,11 @@ See [note](`m:megaco_user#extra_argument`) above about the `Extra` argument in SegCompl :: asn1_NOVALUE | 'NULL'. -doc """ This function is called when a segment reply has been received if the -[segment_reply_ind](`m:megaco#conn_info`) config option has been set to true. +[segment_reply_ind](`megaco:conn_info/2`) config option has been set to true. This is in effect a progress report. -See [note](`m:megaco_user#extra_argument`) above about the `Extra` argument in +See [note](#extra_argument) above about the `Extra` argument in [`handle_segment_reply/6`](`c:handle_segment_reply/6`). """. -callback handle_segment_reply(ConnHandle, From 16dd9fbe87e7ed2b463551cd1ae70997ef9ddf65 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Tue, 5 Nov 2024 12:58:54 +0100 Subject: [PATCH 15/17] snmp: Remove trailing anchors These anchors were used a long time ago to point to the function after the current function, but their use have become obsolete with the usage of ex_doc. --- lib/snmp/src/agent/snmp_community_mib.erl | 4 ---- lib/snmp/src/agent/snmp_framework_mib.erl | 2 -- lib/snmp/src/agent/snmp_view_based_acm_mib.erl | 2 +- lib/snmp/src/agent/snmpa_conf.erl | 3 --- lib/snmp/src/agent/snmpa_error.erl | 2 -- 5 files changed, 1 insertion(+), 12 deletions(-) diff --git a/lib/snmp/src/agent/snmp_community_mib.erl b/lib/snmp/src/agent/snmp_community_mib.erl index f0c0a0f18d6d..d093e7bcb0f7 100644 --- a/lib/snmp/src/agent/snmp_community_mib.erl +++ b/lib/snmp/src/agent/snmp_community_mib.erl @@ -26,7 +26,6 @@ SNMP-COMMUNITY-MIB, and functions for configuring the database. The configuration files are described in the SNMP User's Manual. -[](){: #configure } """. %% Avoid warning for local function error/1 clashing with autoimported BIF. @@ -115,7 +114,6 @@ files are found. The configuration file read is: `community.conf`. -[](){: #reconfigure } """. -spec configure(ConfDir) -> snmp:void() when ConfDir :: string(). @@ -169,7 +167,6 @@ files are found. The configuration file read is: `community.conf`. -[](){: #add_community } """. -spec reconfigure(ConfDir) -> snmp:void() when ConfDir :: string(). @@ -294,7 +291,6 @@ Adds a community to the agent config. Equivalent to one line in the With the `EngineId` argument it is possible to override the configured engine-id (SNMP-FRAMEWORK-MIB). -[](){: #delete_community } """. -doc(#{since => <<"OTP R14B03">>}). -spec add_community(Idx, CommName, SecName, EngineId, CtxName, TransportTag) -> diff --git a/lib/snmp/src/agent/snmp_framework_mib.erl b/lib/snmp/src/agent/snmp_framework_mib.erl index abd3f749c45a..4e73c2ad038d 100644 --- a/lib/snmp/src/agent/snmp_framework_mib.erl +++ b/lib/snmp/src/agent/snmp_framework_mib.erl @@ -227,7 +227,6 @@ This function is called from the supervisor at system start-up. Creates the necessary objects in the database if they do not exist. It does not destroy any old values. -[](){: #add_context } """. -spec init() -> snmp:void(). @@ -642,7 +641,6 @@ table_del_row(Tab, Key) -> Adds a context to the agent config. Equivalent to one line in the `context.conf` file. -[](){: #delete_context } """. -spec add_context(Ctx) -> {ok, Key} | {error, Reason} when Ctx :: string(), diff --git a/lib/snmp/src/agent/snmp_view_based_acm_mib.erl b/lib/snmp/src/agent/snmp_view_based_acm_mib.erl index 27650c344021..f9f5ca7639c2 100644 --- a/lib/snmp/src/agent/snmp_view_based_acm_mib.erl +++ b/lib/snmp/src/agent/snmp_view_based_acm_mib.erl @@ -294,7 +294,7 @@ called, is the data from the configuration files. All `snmp` counters are set to zero. If an error is found in the configuration file, it is reported using the -function [config_err/2](`m:snmpa_error#config_err`) of the error report module, +function [config_err/2](`snmpa_error:config_err/2`) of the error report module, and the function fails with the reason `configuration_error`. `ConfDir` is a string which points to the directory where the configuration diff --git a/lib/snmp/src/agent/snmpa_conf.erl b/lib/snmp/src/agent/snmpa_conf.erl index 6dc34d3d0409..0b1a63d35d62 100644 --- a/lib/snmp/src/agent/snmpa_conf.erl +++ b/lib/snmp/src/agent/snmpa_conf.erl @@ -1359,7 +1359,6 @@ call: See [Target Parameters Definitions](snmp_agent_config_files.md#target_params) for more info. -[](){: #target_params_entry_2 } """. -spec target_params_entry(Name, Vsn) -> TargetParamsEntry when Name :: snmp_target_mib:name(), @@ -1396,7 +1395,6 @@ Where `MPModel` and `SecModel` is mapped from `Vsn`, see above. See [Target Parameters Definitions](snmp_agent_config_files.md#target_params) for more info. -[](){: #target_params_entry_4 } """. -spec target_params_entry(Name, Vsn, SecName, SecLevel) -> TargetParamsEntry when @@ -1875,7 +1873,6 @@ Create an (access) entry for the agent vacm config file, `vacm.conf`. See [MIB Views for VACM](snmp_agent_config_files.md#vacm) for more info. -[](){: #vacm_s2g_entry } """. -spec vacm_acc_entry(GroupName, Prefix, SecModel, SecLevel, Match, RV, WV, NV) -> VacmAccEntry when diff --git a/lib/snmp/src/agent/snmpa_error.erl b/lib/snmp/src/agent/snmpa_error.erl index 97c8fbc0e2c8..43e662d49fab 100644 --- a/lib/snmp/src/agent/snmpa_error.erl +++ b/lib/snmp/src/agent/snmpa_error.erl @@ -55,7 +55,6 @@ if a user defined instrumentation function returns erroneous. `Format` and `Args` are as in `io:format(Format, Args)`. -[](){: #user_err } """. -spec user_err(Format, Args) -> snmp:void() when Format :: string(), @@ -77,7 +76,6 @@ example if a syntax error is found in a configuration file. `Format` and `Args` are as in `io:format(Format, Args)`. -[](){: #config_err } """. -spec config_err(Format, Args) -> snmp:void() when Format :: string(), From c53a77ca0e3ba3316a94be4de1ef98b91dd263dd Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Tue, 5 Nov 2024 12:59:01 +0100 Subject: [PATCH 16/17] tftp: Remove trailing anchors These anchors were used a long time ago to point to the function after the current function, but their use have become obsolete with the usage of ex_doc. --- lib/tftp/src/tftp.erl | 5 ----- 1 file changed, 5 deletions(-) diff --git a/lib/tftp/src/tftp.erl b/lib/tftp/src/tftp.erl index 8378b00186f9..ad9a9284e9ef 100644 --- a/lib/tftp/src/tftp.erl +++ b/lib/tftp/src/tftp.erl @@ -100,7 +100,6 @@ options). This implies that the (new) client will be served by the already ongoing connection on the server side. By not setting up yet another connection, in parallel with the ongoing one, the server consumes less resources. -[](){: #prepare } """. %%------------------------------------------------------------------- @@ -246,7 +245,6 @@ performed. `AcceptedOptions` is sent to the server, which replies with the options that it accepts. These are then forwarded to `open/4` as `SuggestedOptions`. -[](){: #open } """. -doc(#{since => <<"OTP 18.1">>}). @@ -269,7 +267,6 @@ On the server side, where there is no preceding `prepare/5` call, no new options can be added, but those present in `SuggestedOptions` can be omitted or replaced with new values in `AcceptedOptions`. -[](){: #read } """. -doc(#{title => <<"Client API">>, @@ -292,7 +289,6 @@ clean up after the aborted file transfer, such as closing open file descriptors, and so on. In both cases there will be no more calls to any of the callback functions. -[](){: #write } """. -doc(#{since => <<"OTP 18.1">>}). -callback read(State :: term()) -> {more, binary(), NewState :: term()} | @@ -308,7 +304,6 @@ clean up after the aborted file transfer, such as closing open file descriptors, and so on. In both cases there will be no more calls to any of the callback functions. -[](){: #abort } """. -doc(#{since => <<"OTP 18.1">>}). -callback write(binary(), State :: term()) -> From 031eb6fc0996b08a62bfa5ae5ea865d73eb09853 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Tue, 5 Nov 2024 17:00:17 +0100 Subject: [PATCH 17/17] fixup! diameter: Fix broken doc signatures --- lib/diameter/src/transport/diameter_sctp.erl | 8 +++----- 1 file changed, 3 insertions(+), 5 deletions(-) diff --git a/lib/diameter/src/transport/diameter_sctp.erl b/lib/diameter/src/transport/diameter_sctp.erl index 2b23190a7ae4..1b18afbe1226 100644 --- a/lib/diameter/src/transport/diameter_sctp.erl +++ b/lib/diameter/src/transport/diameter_sctp.erl @@ -161,8 +161,6 @@ be specified as the value of a transport_module option to %% --------------------------------------------------------------------------- -doc """ -start(TypeRef, Svc, Options) - The start function required by `m:diameter_transport`. Options `raddr` and `rport` specify the remote address and port for a connecting @@ -226,14 +224,14 @@ connecting transport. -> {ok, pid(), [inet:ip_address()]} when Ref :: diameter:transport_ref(). -start(T, Svc, Opts) - when is_list(Opts) -> +start(TypeRef, Svc, Options) + when is_list(Options) -> #diameter_service{capabilities = Caps, pid = Pid} = Svc, diameter_sctp_sup:start(), %% start supervisors on demand Addrs = Caps#diameter_caps.host_ip_address, - s(T, Addrs, Pid, Opts). + s(TypeRef, Addrs, Pid, Options). %% A listener spawns transports either as a consequence of this call %% when there is not yet an association to assign it, or at comm_up on