File 2881-Rework-simplify-examples.patch of Package erlang

From 1dd926971410c5dd5252347dbbd0831681311522 Mon Sep 17 00:00:00 2001
From: Anders Svensson <anders@erlang.org>
Date: Sat, 25 Jan 2020 23:08:49 +0100
Subject: [PATCH 01/11] Rework/simplify examples

Make each example stand on its own by removing the common node module
that just made for more difficult reading, and redo the fairly confusing
transport config: now it's just a list of transport options as passed to
diameter:add_transport/2, along with some syntactic sugar for
transport_module/transport_config pairs.

Also add a healthy README, that should probably be merged into the
documentation.
---
 lib/diameter/examples/code/GNUmakefile   |   4 +-
 lib/diameter/examples/code/README        | 105 ++++++++++++++++
 lib/diameter/examples/code/client.erl    | 171 +++++++++++++++++---------
 lib/diameter/examples/code/client_cb.erl |  29 ++---
 lib/diameter/examples/code/node.erl      | 202 -------------------------------
 lib/diameter/examples/code/relay.erl     |  73 ++++++-----
 lib/diameter/examples/code/relay_cb.erl  |  55 +++++----
 lib/diameter/examples/code/server.erl    | 121 +++++++++++++-----
 lib/diameter/examples/code/server_cb.erl | 101 +++++++++-------
 lib/diameter/src/modules.mk              |   3 +-
 10 files changed, 457 insertions(+), 407 deletions(-)
 create mode 100644 lib/diameter/examples/code/README
 delete mode 100644 lib/diameter/examples/code/node.erl

diff --git a/lib/diameter/examples/code/GNUmakefile b/lib/diameter/examples/code/GNUmakefile
index f5c2e5f869..c0be5b59f4 100644
--- a/lib/diameter/examples/code/GNUmakefile
+++ b/lib/diameter/examples/code/GNUmakefile
@@ -1,7 +1,7 @@
 #
 # %CopyrightBegin%
 #
-# Copyright Ericsson AB 2010-2015. All Rights Reserved.
+# Copyright Ericsson AB 2010-2020. All Rights Reserved.
 #
 # Licensed under the Apache License, Version 2.0 (the "License");
 # you may not use this file except in compliance with the License.
@@ -21,7 +21,7 @@
 EXAMPLES  = client server relay # redirect proxy
 
 CALLBACKS = $(EXAMPLES:%=%_cb)
-MODULES   = node $(EXAMPLES) $(EXAMPLES:%=%_cb)
+MODULES   = $(EXAMPLES) $(EXAMPLES:%=%_cb)
 
 BEAM = $(MODULES:%=%.beam)
 
diff --git a/lib/diameter/examples/code/README b/lib/diameter/examples/code/README
new file mode 100644
index 0000000000..b639849390
--- /dev/null
+++ b/lib/diameter/examples/code/README
@@ -0,0 +1,105 @@
+
+This directory contains small examples of simple Diameter nodes. They
+don't do everything a real node should do obviously, but they're a
+starting point.
+
+Each example consists of an interface module with functions to start
+and stop a service and add transport, and a corresponding callback
+module for the Diameter application the service configures. A real
+node might support multiple Diameter applications, either with the
+same callback or sharing a common callback, maybe using extra
+arguments to distinguish between callbacks for the different
+applications.
+
+The interface functions are named start, stop, connect, and listen;
+the client example also has a call function that sends an example
+message. Service names should be atoms in these modules (since the
+default setting of Origin-Host assumes this), but doesn't need to be
+in general. Options are passed directly to diameter:start_service/2
+and diameter:add_transport/2, with some additional convenience options
+for the latter; in particular, the atoms tcp and sctp to connect to or
+listen on default endpoints (127.0.01:3868), or tuples with protocol
+and another endpoint {eg. {tcp, {192,168,1,5}, 3869}. This convenience
+makes the simplest usage like this in an Erlang shell:
+
+  diameter:start().
+  server:start().
+  server:listen(tcp).
+  client:start().
+  client:connect(tcp).
+  client:call().
+
+Or put a relay between the client and server:
+
+  diameter:start().
+  server:start().
+  server:listen(sctp).
+  relay:start().
+  relay:connect(sctp).
+  relay:listen(tcp).
+  client:start().
+  client:connect(tcp).
+  client:call().
+
+Most services should probably set the following options, which have
+been added to solve various problems over the years, while the
+defaults have not been changed for backwards compatibility.
+
+  {decode_format, map}
+
+      Provide decoded messages in #diameter_packet.msg of a
+      handle_request or handle_answer callback in the form [Name | Avps],
+      where Name is the atom() name of the message in the (Diameter)
+      application dictionary in question (eg. 'ACR') and Avps is a map
+      of AVP values. This avoids compile-time dependencies on the
+      generated records and their (generally) long-winded names. The
+      hrl files generated from dictionaries are best avoided.
+
+  {restrict_connections, false}
+
+      Accept multiple connections with the same peer. By default,
+      diameter will only accept a single connection with a given peer,
+      which the Diameter RFC can be interpreted as requiring. In
+      practice, wanting multiple connections to the same peer is
+      common.
+
+  {string_decode, false}
+
+      Disable the decoding of string-ish Diameter types to Erlang
+      strings, leaving them as binary(). Strings can be costly if
+      decoded Diameter messages are passed between processes.
+
+  {strict_mbit, false}
+
+      Relax the interpretation of the M-bit so that an AVP setting
+      this bit is not regarded as a 5001 error when the message
+      grammar in question doesn't explicitly list the AVP. Without
+      this, a Redirect-Host AVP received in a 3006
+      (DIAMETER_REDIRECT_INDICATION) answer-message from a redirect
+      agent will be treated as error, and there have been other
+      situations in which the default value has caused problems (or at
+      least surprise).
+
+  {call_mutates_state, false}    (on each configured application)
+
+      Avoid pick_peer and subsequent callbacks going through a single
+      process, which can be a bottleneck. Better to use the tid() of
+      an ets table as (immutable) state, for example.
+
+Other options that are particularly useful/necessary in some
+situations are:
+
+  pool_size - Create a pool of accepting processes for a listening
+              transport, to avoid refused connections when many peers
+              connect simultaneously. Can also be used on a connecting
+              transport to establish multiple connections with a
+              single call to diameter:add_transport/2.
+
+  sequence  - Ensure unique End-to-End and Hop-by-Hop identifiers over
+              a cluster of Erlang nodes.
+
+  share_peers       - Share peer connections across a cluster of
+  use_shared_peers    Erlang nodes.
+
+  spawn_opt - Replace diameter's spawning of a new handler process for
+              each request by something else: diameter_dist is an example.
diff --git a/lib/diameter/examples/code/client.erl b/lib/diameter/examples/code/client.erl
index 0864919cdd..04c91e37fa 100644
--- a/lib/diameter/examples/code/client.erl
+++ b/lib/diameter/examples/code/client.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2010-2017. All Rights Reserved.
+%% Copyright Ericsson AB 2010-2020. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -18,120 +18,173 @@
 %% %CopyrightEnd%
 %%
 
+-module(client).
+
 %%
-%% An example Diameter client that can sends base protocol RAR
+%% An example Diameter client that can sends base protocol ACR
 %% requests to a connected peer.
 %%
-%% The simplest usage is as follows this to connect to a server
-%% listening on the default port on the local host, assuming diameter
-%% is already started (eg. diameter:start()).
+%% Simplest usage to connect to a server listening on TCP at
+%% 127.0.0.1:3868:
 %%
 %%   client:start().
 %%   client:connect(tcp).
 %%   client:call().
 %%
-%% The first call starts the a service with the default name of
-%% ?MODULE, the second defines a connecting transport that results in
-%% a connection to the peer (if it's listening), the third sends it a
-%% RAR and returns the answer.
-%%
-
--module(client).
-
--include_lib("diameter/include/diameter.hrl").
 
 -export([start/1,     %% start a service
          start/2,     %%
          connect/2,   %% add a connecting transport
-         call/1,      %% send using the record encoding
-         cast/1,      %% send using the list encoding and detached
+         call/2,      %% send a request
          stop/1]).    %% stop a service
-%% A real application would typically choose an encoding and whether
-%% they want the call to return the answer or not. Sending with
-%% both the record and list encoding here, one detached and one not,
-%% is just for demonstration purposes.
 
 %% Convenience functions using the default service name.
 -export([start/0,
          connect/1,
          stop/0,
          call/0,
-         cast/0]).
+         call/1]).
 
 -define(DEF_SVC_NAME, ?MODULE).
 -define(L, atom_to_list).
+-define(LOOPBACK, {127,0,0,1}).
 
-%% The service configuration. As in the server example, a client
-%% supporting multiple Diameter applications may or may not want to
-%% configure a common callback module on all applications.
+%% Service configuration.
 -define(SERVICE(Name), [{'Origin-Host', ?L(Name) ++ ".example.com"},
                         {'Origin-Realm', "example.com"},
                         {'Vendor-Id', 0},
                         {'Product-Name', "Client"},
                         {'Auth-Application-Id', [0]},
-                        {string_decode, false},
                         {decode_format, map},
+                        {restrict_connections, false},
+                        {strict_mbit, false},
+                        {string_decode, false},
                         {application, [{alias, common},
                                        {dictionary, diameter_gen_base_rfc6733},
-                                       {module, client_cb}]}]).
+                                       {module, client_cb},
+                                       {answer_errors, callback},
+                                       {call_mutates_state, false}]}]).
 
-%% start/1
+%% start/2
 
-start(Name)
-  when is_atom(Name) ->
-    start(Name, []);
+start(Name, Opts) ->
+    Defaults = [T || {K,_} = T <- ?SERVICE(Name),
+                     not lists:keymember(K, 1, Opts)],
+    diameter:start_service(Name, Opts ++ Defaults).
 
-start(Opts)
-  when is_list(Opts) ->
+%% start/1
+
+start(Opts) ->
     start(?DEF_SVC_NAME, Opts).
 
 %% start/0
 
 start() ->
-    start(?DEF_SVC_NAME).
+    start(?DEF_SVC_NAME, []).
 
-%% start/2
+%% connect/1
 
-start(Name, Opts) ->
-    node:start(Name, Opts ++ [T || {K,_} = T <- ?SERVICE(Name),
-                                   false == lists:keymember(K, 1, Opts)]).
+connect(Opts) ->
+    connect(?DEF_SVC_NAME, Opts).
 
 %% connect/2
 
+connect(Name, Opts)
+  when is_list(Opts) ->
+    diameter:add_transport(Name, {connect, lists:flatmap(fun opts/1, Opts)});
+
+%% backwards compatibility with old config
+connect(Name, {T, Opts}) ->
+    connect(Name, [T | Opts]);
 connect(Name, T) ->
-    node:connect(Name, T).
+    connect(Name, [T]).
 
-connect(T) ->
-    connect(?DEF_SVC_NAME, T).
+%% call/2
 
-%% call/1
+call(Name, #{'Session-Id' := _} = Avps) ->
+    Defaults = #{'Destination-Realm' => "example.com",
+                 'Accounting-Record-Type' => 1,  %% EVENT_RECORD
+                 'Accounting-Record-Number' => 0},
+    ACR = ['ACR' | maps:merge(Defaults, Avps)],
+    diameter:call(Name, common, ACR, []);
 
-call(Name) ->
-    SId = diameter:session_id(?L(Name)),
-    RAR = ['RAR' | #{'Session-Id' => SId,
-                     'Auth-Application-Id' => 0,
-                     'Re-Auth-Request-Type' => 0}],
-    diameter:call(Name, common, RAR, []).
+call(Name, #{} = Avps) ->
+    call(Name, Avps#{'Session-Id' => diameter:session_id(?L(Name))});
 
-call() ->
-    call(?DEF_SVC_NAME).
+call(Name, Avps) ->
+    call(Name, maps:from_list(Avps)).
 
-%% cast/1
+%% call/1
+
+call(Avps) ->
+    call(?DEF_SVC_NAME, Avps).
 
-cast(Name) ->
-    SId = diameter:session_id(?L(Name)),
-    RAR = ['RAR', {'Session-Id', SId},
-                  {'Auth-Application-Id', 0},
-                  {'Re-Auth-Request-Type', 1}],
-    diameter:call(Name, common, RAR, [detach]).
+%% call/0
 
-cast() ->
-    cast(?DEF_SVC_NAME).
+call() ->
+    call(?DEF_SVC_NAME, #{}).
 
 %% stop/1
 
 stop(Name) ->
-    node:stop(Name).
+    diameter:stop_service(Name).
 
 stop() ->
     stop(?DEF_SVC_NAME).
+
+%% ===========================================================================
+
+%% opts/1
+%%
+%% Map some terms to transport_module/transport_config pairs as a
+%% convenience, pass everything else unmodified.
+
+opts(T)
+  when T == any;
+       T == tcp;
+       T == sctp ->
+   opts({T, loopback, 3868});
+
+opts({T, RA, RP}) ->
+    opts({T, [], RA, RP});
+
+opts({T, loopback, RA, RP}) ->
+    opts({T, ?LOOPBACK, RA, RP});
+
+opts({T, LA, RA, RP})
+  when is_tuple(LA) ->
+    opts({T, [{ip, LA}], RA, RP});
+
+opts({any, Opts, RA, RP}) ->
+    All = Opts ++ opts(RA, RP),
+    [{transport_module, diameter_sctp},
+     {transport_config, All, 2000},
+     {transport_module, diameter_tcp},
+     {transport_config, All}];
+
+opts({tcp, Opts, RA, RP}) ->
+    opts({diameter_tcp, Opts, RA, RP});
+
+opts({sctp, Opts, RA, RP}) ->
+    opts({diameter_sctp, Opts, RA, RP});
+
+opts({Mod, Opts, loopback, RP}) ->
+    opts({Mod, Opts, ?LOOPBACK, RP});
+
+opts({Mod, Opts, RA, default}) ->
+    opts({Mod, Opts, RA, 3868});
+
+opts({Mod, Opts, RA, RP}) ->
+    [{transport_module, Mod},
+     {transport_config, opts(RA, RP) ++ Opts}];
+
+opts(T) ->
+    [T].
+
+%% opts/2
+
+opts(loopback, RP) ->
+    opts(?LOOPBACK, RP);
+
+opts(RA, RP) ->
+    [{raddr, RA}, {rport, RP}, {reuseaddr, true}].
diff --git a/lib/diameter/examples/code/client_cb.erl b/lib/diameter/examples/code/client_cb.erl
index af2d4d6da7..7721c47a9a 100644
--- a/lib/diameter/examples/code/client_cb.erl
+++ b/lib/diameter/examples/code/client_cb.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2010-2017. All Rights Reserved.
+%% Copyright Ericsson AB 2010-2020. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -21,7 +21,6 @@
 -module(client_cb).
 
 -include_lib("diameter/include/diameter.hrl").
--include_lib("diameter/include/diameter_gen_base_rfc3588.hrl").
 
 %% diameter callbacks
 -export([peer_up/3,
@@ -50,28 +49,16 @@ pick_peer([Peer | _], _, _SvcName, _State) ->
 
 %% prepare_request/3
 
-prepare_request(#diameter_packet{msg = ['RAR' = T | Avps]}, _, {_, Caps}) ->
-    #diameter_caps{origin_host = {OH, DH},
-                   origin_realm = {OR, DR}}
+prepare_request(#diameter_packet{msg = [Name | Avps]}, _, {_, Caps}) ->
+    #diameter_caps{origin_host = {OH, _},
+                   origin_realm = {OR, _}}
         = Caps,
-
-    {send, [T | if is_map(Avps) ->
-                        Avps#{'Origin-Host' => OH,
-                              'Origin-Realm' => OR,
-                              'Destination-Host' => DH,
-                              'Destination-Realm' => DR};
-                   is_list(Avps) ->
-                        [{'Origin-Host', OH},
-                         {'Origin-Realm', OR},
-                         {'Destination-Host', DH},
-                         {'Destination-Realm', DR}
-                         | Avps]
-                end]}.
+    {send, [Name | Avps#{'Origin-Host' => OH, 'Origin-Realm' => OR}]}.
 
 %% prepare_retransmit/3
 
-prepare_retransmit(Packet, SvcName, Peer) ->
-    prepare_request(Packet, SvcName, Peer).
+prepare_retransmit(Pkt, _SvcName, _Peer) ->
+    {send, Pkt}.
 
 %% handle_answer/4
 
@@ -86,4 +73,4 @@ handle_error(Reason, _Request, _SvcName, _Peer) ->
 %% handle_request/3
 
 handle_request(_Packet, _SvcName, _Peer) ->
-    erlang:error({unexpected, ?MODULE, ?LINE}).
+    {answer_message, 3001}.  %% DIAMETER_COMMAND_UNSUPPORTED
diff --git a/lib/diameter/examples/code/node.erl b/lib/diameter/examples/code/node.erl
deleted file mode 100644
index 77810bf893..0000000000
--- a/lib/diameter/examples/code/node.erl
+++ /dev/null
@@ -1,202 +0,0 @@
-%%
-%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2010-2016. All Rights Reserved.
-%%
-%% Licensed under the Apache License, Version 2.0 (the "License");
-%% you may not use this file except in compliance with the License.
-%% You may obtain a copy of the License at
-%%
-%%     http://www.apache.org/licenses/LICENSE-2.0
-%%
-%% Unless required by applicable law or agreed to in writing, software
-%% distributed under the License is distributed on an "AS IS" BASIS,
-%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-%% See the License for the specific language governing permissions and
-%% limitations under the License.
-%%
-%% %CopyrightEnd%
-%%
-
-%%
-%% A library module used by the example Diameter nodes. Does little
-%% more than provide an alternate/simplified transport configuration.
-%%
-
--module(node).
-
--export([start/2,
-         listen/2,
-         connect/2,
-         stop/1]).
-
--export([message/3]).
-
--type protocol()
-   :: tcp | sctp.
-
--type ip_address()
-   :: default
-    | inet:ip_address().
-
--type server_transport()
-   :: protocol()
-    | {protocol(), ip_address(), non_neg_integer()}.
-
--type server_opts()
-   :: server_transport()
-    | {server_transport(), [diameter:transport_opt()]}
-    | [diameter:transport_opt()].
-
--type client_transport()
-   :: protocol() | any
-    | {protocol() | any, ip_address(), non_neg_integer()}
-    | {protocol() | any, ip_address(), ip_address(), non_neg_integer()}.
-
--type client_opts()
-   :: client_transport()
-    | {client_transport(), [diameter:transport_opt()]}
-    | [diameter:transport_opt()].
-
-%% The server_transport() and client_transport() config is just
-%% convenience: arbitrary options can be specifed as a
-%% [diameter:transport_opt()].
-
--define(DEFAULT_PORT, 3868).
-
-%% ---------------------------------------------------------------------------
-%% Interface functions
-%% ---------------------------------------------------------------------------
-
-%% start/2
-
--spec start(diameter:service_name(), [diameter:service_opt()])
-   -> ok
-    | {error, term()}.
-
-start(Name, Opts)
-  when is_atom(Name), is_list(Opts) ->
-    diameter:start_service(Name, Opts).
-
-%% connect/2
-
--spec connect(diameter:service_name(), client_opts())
-   -> {ok, diameter:transport_ref()}
-    | {error, term()}.
-
-connect(Name, Opts)
-  when is_list(Opts) ->
-    diameter:add_transport(Name, {connect, Opts});
-
-connect(Name, {T, Opts}) ->
-    connect(Name, Opts ++ client_opts(T));
-
-connect(Name, T) ->
-    connect(Name, [{connect_timer, 5000} | client_opts(T)]).
-
-%% listen/2
-
--spec listen(diameter:service_name(), server_opts())
-   -> {ok, diameter:transport_ref()}
-    | {error, term()}.
-
-listen(Name, Opts)
-  when is_list(Opts) ->
-    diameter:add_transport(Name, {listen, Opts});
-
-listen(Name, {T, Opts}) ->
-    listen(Name, Opts ++ server_opts(T));
-
-listen(Name, T) ->
-    listen(Name, server_opts(T)).
-
-%% stop/1
-
--spec stop(diameter:service_name())
-   -> ok
-    | {error, term()}.
-
-stop(Name) ->
-    diameter:stop_service(Name).
-
-%% ---------------------------------------------------------------------------
-%% Internal functions
-%% ---------------------------------------------------------------------------
-
-%% server_opts/1
-%%
-%% Return transport options for a listening transport.
-
-server_opts({T, Addr, Port}) ->
-    [{transport_module, tmod(T)},
-     {transport_config, [{reuseaddr, true},
-                         {sender, true},
-                         {message_cb, [fun ?MODULE:message/3, 0]},
-                         {ip, addr(Addr)},
-                         {port, Port}]}];
-
-server_opts(T) ->
-    server_opts({T, loopback, ?DEFAULT_PORT}).
-
-%% client_opts/1
-%%
-%% Return transport options for a connecting transport.
-
-client_opts({T, LA, RA, RP})
-  when T == all;   %% backwards compatibility
-       T == any ->
-    [[S, {C,Os}], T] = [client_opts({P, LA, RA, RP}) || P <- [sctp,tcp]],
-    [S, {C,Os,2000} | T];
-
-client_opts({T, LA, RA, RP}) ->
-    [{transport_module, tmod(T)},
-     {transport_config, [{raddr, addr(RA)},
-                         {rport, RP},
-                         {reuseaddr, true}
-                         | ip(LA)]}];
-
-client_opts({T, RA, RP}) ->
-    client_opts({T, default, RA, RP});
-
-client_opts(T) ->
-    client_opts({T, loopback, loopback, ?DEFAULT_PORT}).
-
-%% ---------------------------------------------------------------------------
-
-tmod(tcp)  -> diameter_tcp;
-tmod(sctp) -> diameter_sctp.
-
-ip(default) ->
-    [];
-ip(loopback) ->
-    [{ip, {127,0,0,1}}];
-ip(Addr) ->
-    [{ip, Addr}].
-
-addr(loopback) ->
-    {127,0,0,1};
-addr(A) ->
-    A.
-
-%% ---------------------------------------------------------------------------
-
-%% message/3
-%%
-%% Simple message callback that limits the number of concurrent
-%% requests on the peer connection in question.
-
-%% Incoming request.
-message(recv, <<_:32, 1:1, _/bits>> = Bin, N) ->
-    [Bin, N < 32, fun ?MODULE:message/3, N+1];
-
-%% Outgoing request.
-message(ack, <<_:32, 1:1, _/bits>>, _) ->
-    [];
-
-%% Incoming answer or request discarded.
-message(ack, _, N) ->
-    [N =< 32, fun ?MODULE:message/3, N-1];
-
-%% Outgoing message or incoming answer.
-message(_, Bin, _) ->
-    [Bin].
diff --git a/lib/diameter/examples/code/relay.erl b/lib/diameter/examples/code/relay.erl
index 806f79915b..ec53ac01f1 100644
--- a/lib/diameter/examples/code/relay.erl
+++ b/lib/diameter/examples/code/relay.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2010-2016. All Rights Reserved.
+%% Copyright Ericsson AB 2010-2020. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -18,81 +18,94 @@
 %% %CopyrightEnd%
 %%
 
+-module(relay).
+
 %%
 %% An example Diameter relay agent.
 %%
-%% Usage to connect to a server listening on the default port over TCP
-%% and to listen on the default port over SCTP is as follows, assuming
-%% diameter is already started (eg. diameter:start()).
+%% Simplets usage to connect to a server listening on TCP at
+%% 127.0.0.1:3868 and listen for connections on TCP at the same
+%% endpoint:
 %%
-%% Eg.  relay:start().
-%%      relay:connect(tcp).
-%%      relay:listen(sctp).
+%%   relay:start().
+%%   relay:connect(tcp).
+%%   relay:listen(sctp).
 %%
 
--module(relay).
-
+%% Interface.
 -export([start/1,
          start/2,
          listen/2,
          connect/2,
          stop/1]).
 
+%% Convenience functions using the default service name.
 -export([start/0,
          listen/1,
          connect/1,
          stop/0]).
 
+%% Default service name.
 -define(DEF_SVC_NAME, ?MODULE).
 
-%% The service configuration.
+%% Service configuration.
 -define(SERVICE(Name), [{'Origin-Host', atom_to_list(Name) ++ ".example.com"},
                         {'Origin-Realm', "example.com"},
                         {'Vendor-Id', 193},
                         {'Product-Name', "RelayAgent"},
                         {'Auth-Application-Id', [16#FFFFFFFF]},
+                        {decode_format, map},
+                        {restrict_connections, false},
                         {string_decode, false},
+                        {strict_mbit, false},
                         {application, [{alias, relay},
                                        {dictionary, diameter_gen_relay},
-                                       {module, relay_cb}]}]).
+                                       {module, relay_cb},
+                                       {call_mutates_state, false}]}]).
 
-%% start/1
+%% start/2
 
-start(Name)
-  when is_atom(Name) ->
-    start(Name, []).
+start(Name, Opts) ->
+    Defaults = [T || {K,_} = T <- ?SERVICE(Name),
+                     not lists:keymember(K, 1, Opts)],
+    diameter:start_service(Name, Opts ++ Defaults).
 
 %% start/1
 
-start() ->
-    start(?DEF_SVC_NAME).
+start(Opts) ->
+    start(?DEF_SVC_NAME, Opts).
 
-%% start/2
+%% start/0
 
-start(Name, Opts) ->
-    node:start(Name, Opts ++ [T || {K,_} = T <- ?SERVICE(Name),
-                                   false == lists:keymember(K, 1, Opts)]).
+start() ->
+    start(?DEF_SVC_NAME, []).
 
 %% listen/2
 
-listen(Name, T) ->
-    node:listen(Name, T).
+listen(Name, Opts) ->
+    server:listen(Name, Opts).
 
-listen(T) ->
-    listen(?DEF_SVC_NAME, T).
+%% listen/1
+
+listen(Opts) ->
+    listen(?DEF_SVC_NAME, Opts).
 
 %% connect/2
 
-connect(Name, T) ->
-    node:connect(Name, T).
+connect(Name, Opts) ->
+    client:connect(Name, Opts).
+
+%% connect/1
 
-connect(T) ->
-    connect(?DEF_SVC_NAME, T).
+connect(Opts) ->
+    connect(?DEF_SVC_NAME, Opts).
 
 %% stop/1
 
 stop(Name) ->
-    node:stop(Name).
+    diameter:stop_service(Name).
+
+%% stop/0
 
 stop() ->
     stop(?DEF_SVC_NAME).
diff --git a/lib/diameter/examples/code/relay_cb.erl b/lib/diameter/examples/code/relay_cb.erl
index 6df1738143..0d56a14401 100644
--- a/lib/diameter/examples/code/relay_cb.erl
+++ b/lib/diameter/examples/code/relay_cb.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2010-2016. All Rights Reserved.
+%% Copyright Ericsson AB 2010-2020. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -21,48 +21,59 @@
 -module(relay_cb).
 
 -include_lib("diameter/include/diameter.hrl").
--include_lib("diameter/include/diameter_gen_base_rfc3588.hrl").
 
 %% diameter callbacks
 -export([peer_up/3,
          peer_down/3,
-         pick_peer/5,
-         prepare_request/4,
-         prepare_retransmit/4,
-         handle_answer/5,
-         handle_error/5,
+         pick_peer/4,
+         prepare_request/3,
+         prepare_retransmit/3,
+         handle_answer/4,
+         handle_error/4,
          handle_request/3]).
 
+%% peer_up/3
+
 peer_up(_SvcName, _Peer, State) ->
     State.
 
+%% peer_down/3
+
 peer_down(_SvcName, _Peer, State) ->
     State.
 
-%% Returning 'relay' from handle_request causes diameter to resend the
-%% incoming request, which leads to pick_peer and prepare_request
-%% callbacks as if sending explicitly. The 'extra' argument is
-%% appended to the argument list for callbacks following from
-%% resending of the request.
+%% handle_request/3
+
+%% Assume the destination is directly connected; filter
+%% correspondingly; don't relay to the sender.
+handle_request(_Pkt, _SvcName, {_, Caps}) ->
+    #diameter_caps{origin_host = {_, OH}}
+        = Caps,
+    {relay, [{timeout, 2000},
+             {filter, {all, [host, realm, {neg, {host, OH}}]}}]}.
 
-handle_request(_Pkt, _SvcName, _Peer) ->
-    {relay, [{timeout, 1000}, {extra, [relayed]}]}.
+%% pick_peer/4
 
-%% diameter will filter the sender in the Peers list.
-pick_peer([Peer | _], _, _SvcName, _State, relayed) ->
+pick_peer([Peer | _], _, _SvcName, _State) ->
     {ok, Peer}.
 
-prepare_request(Pkt, _SvcName, _Peer, relayed) ->
+%% prepare_request/3
+
+prepare_request(Pkt, _SvcName, _Peer) ->
     {send, Pkt}.
 
-prepare_retransmit(Pkt, _SvcName, _Peer, relayed) ->
+%% prepare_request/3
+
+prepare_retransmit(Pkt, _SvcName, _Peer) ->
     {send, Pkt}.
 
-%% diameter expects handle_answer to return the diameter_packet record
-%% containing the answer when called for a relayed request.
+%% handle_answer/4
 
-handle_answer(Pkt, _Request, _SvcName, _Peer, relayed) ->
+%% Relay an answer by returning the first argument.
+handle_answer(Pkt, _Request, _SvcName, _Peer) ->
     Pkt.
 
-handle_error(Reason, _Request, _SvcName, _Peer, relayed) ->
+%% handle_error/4
+
+handle_error(Reason, _Request, _SvcName, _Peer) ->
     {error, Reason}.
diff --git a/lib/diameter/examples/code/server.erl b/lib/diameter/examples/code/server.erl
index a91be70664..6ee49fb678 100644
--- a/lib/diameter/examples/code/server.erl
+++ b/lib/diameter/examples/code/server.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2010-2015. All Rights Reserved.
+%% Copyright Ericsson AB 2010-2020. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -18,23 +18,20 @@
 %% %CopyrightEnd%
 %%
 
+-module(server).
+
 %%
-%% An example Diameter server that can respond to the base protocol
-%% RAR sent by the client example.
+%% An example Diameter server that answers the base protocol ACR sent
+%% by the client example.
 %%
-%% The simplest example to start a server listening on the loopback
-%% address (which will serve the example usage given in client.erl) is
-%% like this assuming diameter is already started (eg. diameter:start()):
+%% Simplest usage to listen on TCP at 127.0.0.1:3868:
 %%
 %%   server:start().
 %%   server:listen(tcp).
 %%
-%% The first call starts a service, the second adds a transport listening
-%% on the default port.
-%%
 
--module(server).
 
+%% Interface.
 -export([start/1,    %% start a service
          start/2,    %%
          listen/2,   %% add a listening transport
@@ -45,6 +42,9 @@
          listen/1,
          stop/0]).
 
+%% Internal callback.
+-export([message/3]).
+
 -define(DEF_SVC_NAME, ?MODULE).
 
 %% The service configuration. In a server supporting multiple Diameter
@@ -55,45 +55,110 @@
                         {'Vendor-Id', 193},
                         {'Product-Name', "Server"},
                         {'Auth-Application-Id', [0]},
+                        {decode_format, map},
                         {restrict_connections, false},
+                        {strict_mbit, false},
                         {string_decode, false},
                         {application, [{alias, common},
                                        {dictionary, diameter_gen_base_rfc6733},
-                                       {module, server_cb}]}]).
+                                       {module, server_cb},
+                                       {call_mutates_state, false}]}]).
 
-%% start/1
+%% start/2
 
-start(Name)
-  when is_atom(Name) ->
-    start(Name, []);
+start(Name, Opts) ->
+    Defaults = [T || {K,_} = T <- ?SERVICE(Name),
+                     not lists:keymember(K, 1, Opts)],
+    diameter:start_service(Name, Opts ++ Defaults).
 
-start(Opts)
-  when is_list(Opts) ->
+%% start/1
+
+start(Opts) ->
     start(?DEF_SVC_NAME, Opts).
 
 %% start/0
 
 start() ->
-    start(?DEF_SVC_NAME).
-
-%% start/2
-
-start(Name, Opts) ->
-    node:start(Name, Opts ++ [T || {K,_} = T <- ?SERVICE(Name),
-                                   false == lists:keymember(K, 1, Opts)]).
+    start(?DEF_SVC_NAME, []).
 
 %% listen/2
 
+listen(Name, Opts)
+  when is_list(Opts) ->
+    diameter:add_transport(Name, {listen, lists:flatmap(fun opts/1, Opts)});
+
+%% backwards compatibility with old config
+listen(Name, {T, Opts}) ->
+    listen(Name, [T | Opts]);
 listen(Name, T) ->
-    node:listen(Name, T).
+    listen(Name, [T]).
 
-listen(T) ->
-    listen(?DEF_SVC_NAME, T).
+%% listen/1
+
+listen(Opts) ->
+    listen(?DEF_SVC_NAME, Opts).
 
 %% stop/1
 
 stop(Name) ->
-    node:stop(Name).
+    diameter:stop_service(Name).
+
+%% stop/0
 
 stop() ->
     stop(?DEF_SVC_NAME).
+
+%% ===========================================================================
+
+%% opts/1
+%%
+%% Map a 3-tuple a transport_module/transport_config pair as a
+%% convenience, pass everything else unmodified.
+
+opts(T)
+  when T == tcp;
+       T == sctp ->
+    opts({T, loopback, default});
+
+opts({tcp, Addr, Port}) ->
+    opts({diameter_tcp, Addr, Port});
+
+opts({sctp, Addr, Port}) ->
+    opts({diameter_sctp, Addr, Port});
+
+opts({Mod, loopback, Port}) ->
+    opts({Mod, {127,0,0,1}, Port});
+
+opts({Mod, Addr, default}) ->
+    opts({Mod, Addr, 3868});
+
+opts({Mod, Addr, Port}) ->
+    [{transport_module, Mod},
+     {transport_config, [{reuseaddr, true},
+                         {sender, true},
+                         {message_cb, {?MODULE, message, [0]}},
+                         {ip, Addr},
+                         {port, Port}]}];
+opts(T) ->
+    [T].
+
+%% message/3
+%%
+%% Simple message callback that limits the number of concurrent
+%% requests on the peer connection in question.
+
+%% Incoming request.
+message(recv, <<_:32, 1:1, _/bits>> = Bin, N) ->
+    [Bin, N < 32, {?MODULE, message, [N+1]}];
+
+%% Outgoing request.
+message(ack, <<_:32, 1:1, _/bits>>, _) ->
+    [];
+
+%% Incoming answer or request discarded.
+message(ack, _, N) ->
+    [N =< 32, {?MODULE, message, [N-1]}];
+
+%% Outgoing message or incoming answer.
+message(_, Bin, _) ->
+    [Bin].
diff --git a/lib/diameter/examples/code/server_cb.erl b/lib/diameter/examples/code/server_cb.erl
index a2fb8fbda6..5662717c00 100644
--- a/lib/diameter/examples/code/server_cb.erl
+++ b/lib/diameter/examples/code/server_cb.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2010-2015. All Rights Reserved.
+%% Copyright Ericsson AB 2010-2020. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -25,7 +25,6 @@
 -module(server_cb).
 
 -include_lib("diameter/include/diameter.hrl").
--include_lib("diameter/include/diameter_gen_base_rfc6733.hrl").
 
 %% diameter callbacks
 -export([peer_up/3,
@@ -37,67 +36,87 @@
          handle_error/4,
          handle_request/3]).
 
--define(UNEXPECTED, erlang:error({unexpected, ?MODULE, ?LINE})).
+%% Raise an error on callbacks that aren't expected.
+-define(ERROR, error({unexpected, ?MODULE, ?LINE})).
+
+%% peer_up/3
 
 peer_up(_SvcName, _Peer, State) ->
     State.
 
+%% peer_down/3
+
 peer_down(_SvcName, _Peer, State) ->
     State.
 
-pick_peer(_, _, _SvcName, _State) ->
-    ?UNEXPECTED.
+%% pick_peer/3
+
+%% Don't let requests be sent, so other request callbacks shouldn't
+%% happen.
+pick_peer(_LocalCandidates, _RemoteCandidates, _SvcName, _State) ->
+    false.
+
+%% prepare_request/3
 
-prepare_request(_, _SvcName, _Peer) ->
-    ?UNEXPECTED.
+prepare_request(_Packet, _SvcName, _Peer) ->
+    ?ERROR.
+
+%% prepare_retransmit/3
 
 prepare_retransmit(_Packet, _SvcName, _Peer) ->
-    ?UNEXPECTED.
+    ?ERROR.
+
+%% handle_answer/4
 
 handle_answer(_Packet, _Request, _SvcName, _Peer) ->
-    ?UNEXPECTED.
+    ?ERROR.
+
+%% handle_error/4
 
 handle_error(_Reason, _Request, _SvcName, _Peer) ->
-    ?UNEXPECTED.
+    ?ERROR.
+
+%% handle_request/3
 
-%% A request whose decode was successful ...
-handle_request(#diameter_packet{msg = Req, errors = []}, _SvcName, {_, Caps})
-  when is_record(Req, diameter_base_RAR) ->
+%% ACR without decode errors.
+handle_request(#diameter_packet{msg = ['ACR' | #{} = Request],
+                                errors = []},
+               _SvcName,
+               {_, Caps}) ->
     #diameter_caps{origin_host = {OH,_},
                    origin_realm = {OR,_}}
         = Caps,
-    #diameter_base_RAR{'Session-Id' = Id,
-                       'Re-Auth-Request-Type' = Type}
-        = Req,
-
-    {reply, #diameter_base_RAA{'Result-Code' = rc(Type),
-                               'Origin-Host' = OH,
-                               'Origin-Realm' = OR,
-                               'Session-Id' = Id}};
-
-%% ... or one that wasn't. 3xxx errors are answered by diameter itself
-%% but these are 5xxx errors for which we must contruct a reply.
-%% diameter will set Result-Code and Failed-AVP's.
-handle_request(#diameter_packet{msg = Req}, _SvcName, {_, Caps})
-  when is_record(Req, diameter_base_RAR) ->
+
+    #{'Session-Id' := Sid,
+      'Accounting-Record-Type' := T,
+      'Accounting-Record-Number' := N}
+        = Request,
+
+    Answer = #{'Result-Code' => 2001,  %% DIAMETER_SUCCESS
+               'Origin-Host' => OH,
+               'Origin-Realm' => OR,
+               'Session-Id' => Sid,
+               'Accounting-Record-Type' => T,
+               'Accounting-Record-Number' => N},
+
+    {reply, ['ACA' | Answer]};
+
+%% ACR with decode errors.
+handle_request(#diameter_packet{msg = ['ACR' | #{} = Request]},
+               _SvcName,
+               {_, Caps}) ->
     #diameter_caps{origin_host = {OH,_},
                    origin_realm = {OR,_}}
         = Caps,
-    #diameter_base_RAR{'Session-Id' = Id}
-        = Req,
 
-    {reply, #diameter_base_RAA{'Origin-Host' = OH,
-                               'Origin-Realm' = OR,
-                               'Session-Id' = Id}};
+    Answer = maps:merge(maps:with(['Session-Id'], Request),
+                        #{'Origin-Host' => OH,
+                          'Origin-Realm' => OR}),
 
-%% Answer that any other message is unsupported.
+    %% Let diameter set Result-Code and Failed-AVP if there were
+    %% decode errors.
+    {reply, ['answer-message' | Answer]};
+
+%% Answer anything else as unsupported.
 handle_request(#diameter_packet{}, _SvcName, _) ->
     {answer_message, 3001}.  %% DIAMETER_COMMAND_UNSUPPORTED
-
-%% Map Re-Auth-Request-Type to Result-Code just for the purpose of
-%% generating different answers.
-
-rc(0) ->
-    2001;  %% DIAMETER_SUCCESS
-rc(_) ->
-    5012.  %% DIAMETER_UNABLE_TO_COMPLY
diff --git a/lib/diameter/src/modules.mk b/lib/diameter/src/modules.mk
index d16292bb88..144d08fcba 100644
--- a/lib/diameter/src/modules.mk
+++ b/lib/diameter/src/modules.mk
@@ -1,7 +1,7 @@
 
 # %CopyrightBegin%
 #
-# Copyright Ericsson AB 2010-2019. All Rights Reserved.
+# Copyright Ericsson AB 2010-2020. All Rights Reserved.
 #
 # Licensed under the Apache License, Version 2.0 (the "License");
 # you may not use this file except in compliance with the License.
@@ -98,7 +98,6 @@ BINS = \
 # Released files relative to ../examples.
 EXAMPLES = \
 	code/GNUmakefile \
-	code/node.erl \
 	code/client.erl \
 	code/client_cb.erl \
 	code/server.erl \
-- 
2.16.4

openSUSE Build Service is sponsored by