File 0777-Fix-service-transport-option-inconsistencies.patch of Package erlang
From ffa9d7194e4c4d188fcec21537eefa696b2174b0 Mon Sep 17 00:00:00 2001
From: Anders Svensson <anders@erlang.org>
Date: Tue, 11 Feb 2020 22:11:52 +0100
Subject: [PATCH 09/11] Fix service/transport option inconsistencies
Service options passed to diameter:add_transport/2 were interpreted as
such, instead of being ignored as the documentation requires, with the
consequence that outgoing and incoming requests saw different values of
some options (eg. decode_format), some were always taken from transport
options (eg. restrict_connections), and others from service options
(eg. share_peers/use_shared_peers). Now ignore service options passed
to diameter:add_transport/2, as the documentation requires.
This behaviour precedes the changes in commit 5f3becad, that the parent
commit addresses, and has probably been the case for some time.
That unknown options passed to diameter:add_transport/2 are ignored
rather than rejected is questionable, but at least one known user makes
use of this to be able to identify transport options returned from
diameter:service_info/2, so it can't just be removed. That service
options in transport configuration isn't rejected outright is probably
even more questionable, but it hasn't been an issue in practice.
The documentation was also a little wrong on which transport options can
be configured on a service, missing transport_config and
transport_module as two that aren't allowed, although these did cause
diameter:start_service/2 to return error as expected. (That function not
accepting unknown options.)
---
lib/diameter/doc/src/diameter.xml | 5 +-
lib/diameter/src/base/diameter_config.erl | 20 +++++---
lib/diameter/src/base/diameter_service.erl | 79 +++++++++++++++++++-----------
3 files changed, 65 insertions(+), 39 deletions(-)
diff --git a/lib/diameter/doc/src/diameter.xml b/lib/diameter/doc/src/diameter.xml
index 0ab6a122cd..aa4eb6ad45 100644
--- a/lib/diameter/doc/src/diameter.xml
+++ b/lib/diameter/doc/src/diameter.xml
@@ -1046,8 +1046,9 @@ each node from which requests are sent.</p>
<tag><c>&transport_opt;</c></tag>
<item>
<p>
-Any transport option except <c>applications</c> or
-<c>capabilities</c>.
+Any transport option except <c>applications</c>,
+<c>capabilities</c>, <c>transport_config</c>, and
+<c>transport_module</c>.
Used as defaults for transport configuration, values passed to
&add_transport; overriding values configured on the service.</p>
</item>
diff --git a/lib/diameter/src/base/diameter_config.erl b/lib/diameter/src/base/diameter_config.erl
index 36ae4c2276..495e57e456 100644
--- a/lib/diameter/src/base/diameter_config.erl
+++ b/lib/diameter/src/base/diameter_config.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2010-2018. 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.
@@ -661,6 +661,9 @@ opt(transport, {transport_module, M}) ->
opt(transport, {transport_config, _, Tmo}) ->
?IS_UINT32(Tmo) orelse Tmo == infinity;
+opt(transport, {transport_config, _}) ->
+ true;
+
opt(transport, {applications, As}) ->
is_list(As);
@@ -720,15 +723,16 @@ opt(_, {K, _})
when K == disconnect_cb;
K == capabilities_cb ->
true;
-opt(transport, {K, _})
- when K == transport_config;
- K == private ->
+opt(transport, {private, _}) ->
true;
-%% Anything else, which is ignored in transport config. This makes
-%% options sensitive to spelling mistakes, but arbitrary options are
-%% passed by some users as a way to identify transports so can't just
-%% do away with it.
+%% Anything else is ignored in transport config. This makes options
+%% sensitive to spelling mistakes and unintentionally passing service
+%% options, but arbitrary options are passed by some users as a way to
+%% identify transports (they can be returned by diameter:service_info/2
+%% for example) so can't just do away with it, although silently
+%% swallowing service options is at least debatable. The documentation
+%% says anything, so accept anything.
opt(K, _) ->
K == transport.
diff --git a/lib/diameter/src/base/diameter_service.erl b/lib/diameter/src/base/diameter_service.erl
index a57b7e7f4b..520a7233cc 100644
--- a/lib/diameter/src/base/diameter_service.erl
+++ b/lib/diameter/src/base/diameter_service.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2010-2018. 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.
@@ -735,29 +735,31 @@ init_peers() ->
%% Alias,
%% TPid}
+%% Valid service options are all 2-tuples.
service_opts(Opts) ->
- remove([{strict_arities, true},
- {avp_dictionaries, []}],
- maps:merge(maps:from_list([{monitor, false} | def_opts()]),
- maps:from_list(Opts))).
+ remove([{strict_arities, true}, {avp_dictionaries, []}],
+ merge(lists:append([[{monitor, false}] | def_opts()]), Opts)).
+
+merge(List1, List2) ->
+ maps:merge(maps:from_list(List1), maps:from_list(List2)).
remove(List, Map) ->
maps:filter(fun(K,V) -> not lists:member({K,V}, List) end,
Map).
-def_opts() -> %% defaults on the service map
- [{share_peers, false},
- {use_shared_peers, false},
- {sequence, {0,32}},
- {restrict_connections, nodes},
- {incoming_maxlen, 16#FFFFFF},
- {strict_arities, true},
- {strict_mbit, true},
- {decode_format, record},
- {avp_dictionaries, []},
- {traffic_counters, true},
- {string_decode, true},
- {spawn_opt, []}].
+def_opts() -> %% defaults on the options map
+ [[{decode_format, record}, %% service options
+ {restrict_connections, nodes},
+ {sequence, {0,32}},
+ {share_peers, false},
+ {strict_arities, true},
+ {string_decode, true},
+ {traffic_counters, true},
+ {use_shared_peers, false}],
+ [{avp_dictionaries, []}, %% common options
+ {incoming_maxlen, 16#FFFFFF},
+ {spawn_opt, []},
+ {strict_mbit, true}]].
mref(false = No) ->
No;
@@ -875,9 +877,9 @@ start(Ref, Type, Opts, N, #state{watchdogT = WatchdogT,
= Svc1
= merge_service(Opts, Svc0),
Svc = binary_caps(Svc1, SD),
- {SOpts, TOpts} = merge_opts(SvcOpts, Opts),
- RecvData = diameter_traffic:make_recvdata([SvcName, PeerT, Apps, SOpts]),
- T = {TOpts, SOpts, RecvData, Svc},
+ {Map, Rest} = merge_opts(SvcOpts, Opts),
+ RecvData = diameter_traffic:make_recvdata([SvcName, PeerT, Apps, Map]),
+ T = {Rest, Map, RecvData, Svc},
Rec = #watchdog{type = Type,
ref = Ref,
options = Opts}, %% original options, returned
@@ -888,14 +890,33 @@ start(Ref, Type, Opts, N, #state{watchdogT = WatchdogT,
[],
N).
-merge_opts(SvcOpts, Opts) ->
- Keys = [K || {K,_} <- def_opts()],
- SO = [T || {K,_} = T <- Opts, lists:member(K, Keys)],
- TO = Opts -- SO,
- {maps:merge(maps:with(Keys, SvcOpts), maps:from_list(SO)),
- TO ++ [T || {K,_} = T <- maps:to_list(SvcOpts),
- not lists:member(K, Keys),
- not lists:keymember(K, 1, Opts)]}.
+%% This is awkward. We have service options that have been passed to
+%% diameter:start_service/2 (minus application and capabilities
+%% options, removed in diameter_config) and transport options passed
+%% to diameter:add_transport/2. The former can include defaults for
+%% the latter, but the latter can also contain arbitrary options that
+%% are just returned by diameter:service_info/2. There's nothing
+%% stopping these arbitrary options from being valid service options,
+%% but these aren't interpreted as such.
+%%
+%% The options are merged (transport defaults have already been merged
+%% into the service options in service_opts/1) and split into a map
+%% for the service options and a few transport options, and a list for
+%% the rest. This is historical convolution. Some options are are
+%% pulled out of the list on the way to starting the transport process
+%% in diameter_peer_fsm, but more work could probably be done here to
+%% simplify things.
+%%
+%% Transport options are not necessarily 2-tuples: the transport_config
+%% 3-tuple means they can't just be turned into a map.
+merge_opts(SOpts, TOpts) ->
+ [SD,TD] = Def = def_opts(),
+ Keys = [K || L <- Def, {K,_} <- L],
+ Opts = [T || {K,_} = T <- TOpts, lists:keymember(K, 1, TD)],
+ {maps:merge(maps:with(Keys, SOpts), maps:from_list(Opts)),%% merge TOpts
+ TOpts ++ [T || {K,_} = T <- maps:to_list(SOpts), %% append SOpts
+ not lists:keymember(K, 1, SD),
+ [] == [A || {A,_} <- TOpts, A == K]]}.
binary_caps(Svc, true) ->
Svc;
--
2.16.4