aboutsummaryrefslogtreecommitdiffstats
path: root/lib/diameter/test
diff options
context:
space:
mode:
Diffstat (limited to 'lib/diameter/test')
-rw-r--r--lib/diameter/test/Makefile6
-rw-r--r--lib/diameter/test/diameter_capx_SUITE.erl82
-rw-r--r--lib/diameter/test/diameter_codec_SUITE.erl2
-rw-r--r--lib/diameter/test/diameter_codec_SUITE_data/diameter_test_unknown.erl2
-rw-r--r--lib/diameter/test/diameter_codec_test.erl173
-rw-r--r--lib/diameter/test/diameter_compiler_SUITE.erl162
-rw-r--r--lib/diameter/test/diameter_examples_SUITE.erl4
-rw-r--r--lib/diameter/test/diameter_traffic_SUITE.erl4
-rw-r--r--lib/diameter/test/diameter_transport_SUITE.erl7
-rw-r--r--lib/diameter/test/diameter_util.erl2
10 files changed, 323 insertions, 121 deletions
diff --git a/lib/diameter/test/Makefile b/lib/diameter/test/Makefile
index 9719c67b32..aff1b18cf8 100644
--- a/lib/diameter/test/Makefile
+++ b/lib/diameter/test/Makefile
@@ -1,4 +1,4 @@
-#
+#
# %CopyrightBegin%
#
# Copyright Ericsson AB 2010-2013. All Rights Reserved.
@@ -76,7 +76,7 @@ any: opt
$(MAKE) -i $(SUITES)
clean:
- rm -f $(TARGET_FILES)
+ rm -f $(TARGET_FILES)
rm -f depend.mk coverspec
realclean: clean
@@ -159,7 +159,7 @@ log:
# ----------------------------------------------------
# Release Targets
-# ----------------------------------------------------
+# ----------------------------------------------------
/%: % force
sed -f release.sed $< > "$(RELSYSDIR)$@"
diff --git a/lib/diameter/test/diameter_capx_SUITE.erl b/lib/diameter/test/diameter_capx_SUITE.erl
index 8c9bb67e61..deabdd720b 100644
--- a/lib/diameter/test/diameter_capx_SUITE.erl
+++ b/lib/diameter/test/diameter_capx_SUITE.erl
@@ -27,6 +27,8 @@
-export([suite/0,
all/0,
groups/0,
+ init_per_suite/1,
+ end_per_suite/1,
init_per_group/2,
end_per_group/2,
init_per_testcase/2,
@@ -56,6 +58,11 @@
peer_down/4]).
-include("diameter.hrl").
+-include("diameter_gen_base_rfc3588.hrl").
+%% Use only the Vendor-Specific-Application-Id record from the base
+%% include, to test the independence of capabilities configuration
+%% from the different definitions of Vendor-Id in RFC's 3588 and RFC
+%% 6733.
%% ===========================================================================
@@ -69,6 +76,11 @@
-define(REALM, "erlang.org").
-define(HOST(Name), Name ++ "." ++ ?REALM).
+%% Application id's that are never agreed upon at capabilities
+%% exchange. Testcase no_common_application references them in order
+%% to exercise Vendor-Specific-Application-Id handling.
+-define(NOAPPS, [1111, 2222, 3333, 4444]).
+
%% Config for diameter:start_service/2.
-define(SERVICE,
[{'Origin-Realm', ?REALM},
@@ -83,7 +95,10 @@
|| {A,D} <- [{base3588, diameter_gen_base_rfc3588},
{acct3588, diameter_gen_base_accounting},
{base6733, diameter_gen_base_rfc6733},
- {acct6733, diameter_gen_acct_rfc6733}]]]).
+ {acct6733, diameter_gen_acct_rfc6733}]]]
+ ++ [{application, [{dictionary, dict(N)},
+ {module, not_really}]}
+ || N <- ?NOAPPS]).
-define(A, list_to_atom).
-define(L, atom_to_list).
@@ -116,6 +131,16 @@ groups() ->
Tc = lists:flatmap(fun tc/1, tc()),
[{D, [], Tc} || D <- ?DICTS].
+init_per_suite(Config) ->
+ lists:foreach(fun load_dict/1, ?NOAPPS),
+ Config.
+
+end_per_suite(_Config) ->
+ [] = [Mod || N <- ?NOAPPS,
+ Mod <- [dict(N)],
+ false <- [code:delete(Mod)]],
+ ok.
+
%% Generate a unique hostname for each testcase so that watchdogs
%% don't prevent a connection from being brought up immediately.
init_per_testcase(Name, Config) ->
@@ -160,7 +185,7 @@ start(_Config) ->
ok = diameter:start().
%% Ensure that both integer and list-valued vendor id's can be
-%% configured in a 'Vendor-Specific-Application-Id, the arity having
+%% configured in a Vendor-Specific-Application-Id, the arity having
%% changed between RFC 3588 and RFC 6733.
vendor_id(_Config) ->
[] = ?util:run([[fun vid/1, V] || V <- [1, [1], [1,2], x]]).
@@ -188,13 +213,13 @@ add_listeners(Config) ->
Acct = [listen(?SERVER,
[{capabilities, [{'Origin-Host', ?HOST(H)},
{'Auth-Application-Id', []}]},
- {applications, [A]},
+ {applications, [A | noapps()]},
{capabilities_cb, [fun server_capx/3, acct]}])
|| {A,H} <- [{acct3588, "acct3588-srv"},
{acct6733, "acct6733-srv"}]],
Base = [listen(?SERVER,
[{capabilities, [{'Origin-Host', ?HOST(H)}]},
- {applications, A},
+ {applications, A ++ noapps()},
{capabilities_cb, [fun server_capx/3, base]}])
|| {A,H} <- [{[base3588, acct3588], "base3588-srv"},
{[base6733, acct6733], "base6733-srv"}]],
@@ -224,15 +249,33 @@ stop(_Config) ->
%% DIAMETER_NO_COMMON_APPLICATION = 5010.
s_no_common_application(Config) ->
- server_closed(Config, fun no_common_application/1, 5010).
+ Vs = [[{'Vendor-Id', 111},
+ {'Auth-Application-Id', [1111]}],
+ #'diameter_base_Vendor-Specific-Application-Id'
+ {'Vendor-Id' = [222],
+ 'Acct-Application-Id' = [2222]}],
+ server_closed(Config,
+ fun(C) -> no_common_application(C,Vs) end,
+ 5010).
c_no_common_application(Config) ->
- client_closed(Config, "acct-srv", fun no_common_application/1, 5010).
-
-no_common_application(Config) ->
+ Vs = [#'diameter_base_Vendor-Specific-Application-Id'
+ {'Vendor-Id' = 333,
+ 'Auth-Application-Id' = [3333]},
+ [{'Vendor-Id', [444]},
+ {'Acct-Application-Id', [4444]}]],
+ client_closed(Config,
+ "acct-srv",
+ fun(C) -> no_common_application(C,Vs) end,
+ 5010).
+
+no_common_application(Config, Vs) ->
[Common, _Acct] = apps(Config),
- connect(Config, acct, [{capabilities, [{'Acct-Application-Id', []}]},
- {applications, [Common]}]).
+ connect(Config,
+ acct,
+ [{capabilities, [{'Acct-Application-Id', []},
+ {'Vendor-Specific-Application-Id', Vs}]},
+ {applications, [Common | noapps()]}]).
%% ====================
%% Ask the base server to speak accounting with an unknown security
@@ -324,6 +367,25 @@ client_reject(Config) ->
%% ===========================================================================
+noapps() ->
+ lists:map(fun dict/1, ?NOAPPS).
+
+dict(N) ->
+ ?A(?L(?MODULE) ++ "_" ++ integer_to_list(N)).
+
+%% Compile and load minimal dictionary modules. These actually have to
+%% exists since diameter will call their id/0 to extract application
+%% id's, failing with app_not_configured if it can't.
+load_dict(N) ->
+ Mod = dict(N),
+ Forms = [{attribute, 1, module, Mod},
+ {attribute, 2, compile, [export_all]},
+ {function, 3, id, 0,
+ [{clause, 4, [], [], [{integer, 4, N}]}]}],
+ {ok, Mod, Bin, []} = compile:forms(Forms, [return]),
+ {module, Mod} = code:load_binary(Mod, Mod, Bin),
+ N = Mod:id().
+
%% server_closed/3
server_closed(Config, F, RC) ->
diff --git a/lib/diameter/test/diameter_codec_SUITE.erl b/lib/diameter/test/diameter_codec_SUITE.erl
index 2e219bbb10..cd8ca41f66 100644
--- a/lib/diameter/test/diameter_codec_SUITE.erl
+++ b/lib/diameter/test/diameter_codec_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2010-2011. All Rights Reserved.
+%% Copyright Ericsson AB 2010-2013. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
diff --git a/lib/diameter/test/diameter_codec_SUITE_data/diameter_test_unknown.erl b/lib/diameter/test/diameter_codec_SUITE_data/diameter_test_unknown.erl
index 49f2158b1a..cdf0cf55e1 100644
--- a/lib/diameter/test/diameter_codec_SUITE_data/diameter_test_unknown.erl
+++ b/lib/diameter/test/diameter_codec_SUITE_data/diameter_test_unknown.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2010-2011. All Rights Reserved.
+%% Copyright Ericsson AB 2010-2013. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
diff --git a/lib/diameter/test/diameter_codec_test.erl b/lib/diameter/test/diameter_codec_test.erl
index 24d4c7665e..0b4568a9e5 100644
--- a/lib/diameter/test/diameter_codec_test.erl
+++ b/lib/diameter/test/diameter_codec_test.erl
@@ -1,3 +1,4 @@
+%% coding: utf-8
%%
%% %CopyrightBegin%
%%
@@ -19,7 +20,9 @@
-module(diameter_codec_test).
--compile(export_all).
+-export([base/0,
+ gen/1,
+ lib/0]).
%%
%% Test encode/decode of dictionary-related modules.
@@ -38,37 +41,34 @@
%% Interface.
base() ->
- [] = run([{?MODULE, [base, T]} || T <- [zero, decode]]).
+ [] = run([[fun base/1, T] || T <- [zero, decode]]).
gen(Mod) ->
Fs = [{Mod, F, []} || F <- [name, id, vendor_id, vendor_name]],
- [] = run(Fs ++ [{?MODULE, [gen, Mod, T]} || T <- [messages,
- command_codes,
- avp_types,
- grouped,
- enum,
- import_avps,
- import_groups,
- import_enums]]).
+ [] = run(Fs ++ [[fun gen/2, Mod, T] || T <- [messages,
+ command_codes,
+ avp_types,
+ grouped,
+ enum,
+ import_avps,
+ import_groups,
+ import_enums]]).
lib() ->
- Vs = {_,_} = values('Address'),
- [] = run([[fun lib/2, N, Vs] || N <- [1,2]]).
+ Vs = {_,_,_} = values('Address'),
+ [] = run([[fun lib/2, N, Vs] || N <- [{1, true}, {3, false}]]).
%% ===========================================================================
%% Internal functions.
-lib(N, {_,_} = T) ->
- B = 1 == N rem 2,
- [] = run([[fun lib/2, A, B] || A <- element(N,T)]);
+lib({N,B}, {_,_,_} = T) ->
+ [] = run([[fun lib/2, A, B] || A <- element(N,T), is_tuple(A)]);
lib(IP, B) ->
- LA = tuple_to_list(IP),
- {SA,Fun} = ip(LA),
- [] = run([[fun lib/4, IP, B, Fun, A] || A <- [IP, SA]]).
+ [] = run([[fun lib/3, IP, B, A] || A <- [IP, ntoa(tuple_to_list(IP))]]).
-lib(IP, B, Fun, A) ->
- try Fun(A) of
+lib(IP, B, A) ->
+ try diameter_lib:ipaddr(A) of
IP when B ->
ok
catch
@@ -76,12 +76,12 @@ lib(IP, B, Fun, A) ->
ok
end.
-ip([_,_,_,_] = A) ->
+ntoa([_,_,_,_] = A) ->
[$.|S] = lists:append(["." ++ integer_to_list(N) || N <- A]),
- {S, fun diameter_lib:ipaddr/1};
-ip([_,_,_,_,_,_,_,_] = A) ->
+ S;
+ntoa([_,_,_,_,_,_,_,_] = A) ->
[$:|S] = lists:flatten([":" ++ io_lib:format("~.16B", [N]) || N <- A]),
- {S, fun diameter_lib:ipaddr/1}.
+ S.
%% ------------------------------------------------------------------------
%% base/1
@@ -90,7 +90,7 @@ ip([_,_,_,_,_,_,_,_] = A) ->
%% ------------------------------------------------------------------------
base(T) ->
- [] = run([{?MODULE, [base, T, F]} || F <- types()]).
+ [] = run([[fun base/2, T, F] || F <- types()]).
%% Ensure that 'zero' values encode only zeros.
base(zero = T, F) ->
@@ -100,32 +100,23 @@ base(zero = T, F) ->
%% Ensure that we can decode what we encode and vice-versa, and that
%% we can't decode invalid values.
base(decode, F) ->
- {Eq, Vs, Ns} = b(values(F)),
- [] = run([{?MODULE, [base_decode, F, Eq, V]} || V <- Vs]),
- [] = run([{?MODULE, [base_invalid, F, Eq, V]} || V <- Ns]).
+ {Ts, Fs, Is} = values(F),
+ [] = run([[fun base_decode/3, F, true, V] || V <- Ts]),
+ [] = run([[fun base_decode/3, F, false, V] || V <- Fs]),
+ [] = run([[fun base_invalid/2, F, V] || V <- Is]).
base_decode(F, Eq, Value) ->
d(fun(X,V) -> diameter_types:F(X,V) end, Eq, Value).
-base_invalid(F, Eq, Value) ->
+base_invalid(F, Value) ->
try
- base_decode(F, Eq, Value),
+ base_decode(F, false, Value),
exit(nok)
catch
error: _ ->
ok
end.
-b({_,_,_} = T) ->
- T;
-b({B,Vs})
- when is_atom(B) ->
- {B,Vs,[]};
-b({Vs,Ns}) ->
- {true, Vs, Ns};
-b(Vs) ->
- {true, Vs, []}.
-
types() ->
[F || {F,2} <- diameter_types:module_info(exports)].
@@ -136,7 +127,7 @@ types() ->
%% ------------------------------------------------------------------------
gen(M, T) ->
- [] = run(lists:map(fun(X) -> {?MODULE, [gen, M, T, X]} end,
+ [] = run(lists:map(fun(X) -> [fun gen/3, M, T, X] end,
fetch(T, dict(M)))).
fetch(T, Spec) ->
@@ -197,18 +188,20 @@ gen(M, enum = T, {Name, ED})
gen(M, T, {?A(Name), lists:map(fun({E,D}) -> {?A(E), D} end, ED)});
gen(M, enum, {Name, ED}) ->
- [] = run([{?MODULE, [enum, M, Name, T]} || T <- ED]);
+ [] = run([[fun enum/3, M, Name, T] || T <- ED]);
gen(M, Tag, {_Mod, L}) ->
T = retag(Tag),
- [] = run([{?MODULE, [gen, M, T, I]} || I <- L]).
+ [] = run([[fun gen/3, M, T, I] || I <- L]).
%% avp_decode/3
avp_decode(Mod, Type, Name) ->
- {Eq, Vs, _} = b(values(Type, Name, Mod)),
- [] = run([{?MODULE, [avp_decode, Mod, Name, Type, Eq, V]}
- || V <- v(Vs)]).
+ {Ts, Fs, _} = values(Type, Name, Mod),
+ [] = run([[fun avp_decode/5, Mod, Name, Type, true, V]
+ || V <- v(Ts)]),
+ [] = run([[fun avp_decode/5, Mod, Name, Type, false, V]
+ || V <- v(Fs)]).
avp_decode(Mod, Name, Type, Eq, Value) ->
d(fun(X,V) -> avp(Mod, X, V, Name, Type) end, Eq, Value).
@@ -250,7 +243,7 @@ v(N, Ord, E, Acc) ->
arity(M, Name, Rname) ->
Rec = M:'#new-'(Rname),
- [] = run([{?MODULE, [arity, M, Name, F, Rec]}
+ [] = run([[fun arity/4, M, Name, F, Rec]
|| F <- M:'#info-'(Rname, fields)]).
arity(M, Name, AvpName, Rec) ->
@@ -299,68 +292,93 @@ z(B) ->
%% tested.)
values('OctetString' = T) ->
- {["", atom_to_list(T)], [-1, 256]};
+ {["", atom_to_list(T)],
+ [],
+ [-1, 256]};
values('Integer32') ->
Mx = (1 bsl 31) - 1,
Mn = -1*Mx,
- {[Mn, 0, random(Mn,Mx), Mx], [Mn - 1, Mx + 1]};
+ {[Mn, 0, random(Mn,Mx), Mx],
+ [],
+ [Mn - 1, Mx + 1]};
values('Integer64') ->
Mx = (1 bsl 63) - 1,
Mn = -1*Mx,
- {[Mn, 0, random(Mn,Mx), Mx], [Mn - 1, Mx + 1]};
+ {[Mn, 0, random(Mn,Mx), Mx],
+ [],
+ [Mn - 1, Mx + 1]};
values('Unsigned32') ->
M = (1 bsl 32) - 1,
- {[0, random(M), M], [-1, M + 1]};
+ {[0, random(M), M],
+ [],
+ [-1, M + 1]};
values('Unsigned64') ->
M = (1 bsl 64) - 1,
- {[0, random(M), M], [-1, M + 1]};
+ {[0, random(M), M],
+ [],
+ [-1, M + 1]};
values('Float32') ->
E = (1 bsl 8) - 2,
F = (1 bsl 23) - 1,
<<Mx:32/float>> = <<0:1, E:8, F:23>>,
<<Mn:32/float>> = <<1:1, E:8, F:23>>,
- {[0.0, infinity, '-infinity', Mx, Mn], [0]};
+ {[0.0, infinity, '-infinity', Mx, Mn],
+ [],
+ [0]};
values('Float64') ->
E = (1 bsl 11) - 2,
F = (1 bsl 52) - 1,
<<Mx:64/float>> = <<0:1, E:11, F:52>>,
<<Mn:64/float>> = <<1:1, E:11, F:52>>,
- {[0.0, infinity, '-infinity', Mx, Mn], [0]};
+ {[0.0, infinity, '-infinity', Mx, Mn],
+ [],
+ [0]};
values('Address') ->
{[{255,0,random(16#FF),1}, {65535,0,0,random(16#FFFF),0,0,0,1}],
- [{256,0,0,1}, {65536,0,0,0,0,0,0,1}]};
+ ["127.0.0.1", "FFFF:FF::1.2.3.4"],
+ [{256,0,0,1}, {65536,0,0,0,0,0,0,1}, "256.0.0.1", "10000::1"]};
values('DiameterIdentity') ->
- {["x", "diameter.com"], [""]};
+ {["x", "diameter.com"],
+ [],
+ [""]};
values('DiameterURI') ->
- {false, ["aaa" ++ S ++ "://diameter.se" ++ P ++ Tr ++ Pr
- || S <- ["", "s"],
- P <- ["", ":1234"],
- Tr <- ["" | [";transport=" ++ X
- || X <- ["tcp", "sctp", "udp"]]],
- Pr <- ["" | [";protocol=" ++ X
- || X <- ["diameter","radius","tacacs+"]]]]};
+ {[],
+ ["aaa" ++ S ++ "://diameter.se" ++ P ++ Tr ++ Pr
+ || S <- ["", "s"],
+ P <- ["", ":1234"],
+ Tr <- ["" | [";transport=" ++ X
+ || X <- ["tcp", "sctp", "udp"]]],
+ Pr <- ["" | [";protocol=" ++ X
+ || X <- ["diameter","radius","tacacs+"]]]],
+ []};
values(T)
when T == 'IPFilterRule';
T == 'QoSFilterRule' ->
- ["deny in 0 from 127.0.0.1 to 10.0.0.1"];
+ {["deny in 0 from 127.0.0.1 to 10.0.0.1"],
+ [],
+ []};
%% RFC 3629 defines the UTF-8 encoding of U+0000 through U+10FFFF with the
%% exception of U+D800 through U+DFFF.
values('UTF8String') ->
+ S = "ᚠᚢᚦᚨᚱᚲ",
+ B = unicode:characters_to_binary(S),
{[[],
+ S,
lists:seq(0,16#1FF),
[0,16#D7FF,16#E000,16#10FFFF],
[random(16#D7FF), random(16#E000,16#10FFFF)]],
+ [B, [B, S, hd(S)], [S, B]],
[[-1],
[16#D800],
[16#DFFF],
@@ -372,6 +390,7 @@ values('Time') ->
{{2036,2,7},{6,28,15}},
{{2036,2,7},{6,28,16}}, %% 19000101T000000 + 2 bsl 31
{{2104,2,26},{9,42,23}}],
+ [],
[{{1968,1,20},{3,14,7}},
{{2104,2,26},{9,42,24}}]}. %% 19000101T000000 + 3 bsl 31
@@ -382,18 +401,24 @@ values('Time') ->
values('Enumerated', Name, Mod) ->
{_Name, Vals} = lists:keyfind(?S(Name), 1, types(enum, Mod)),
- lists:map(fun({_,N}) -> N end, Vals);
+ {lists:map(fun({_,N}) -> N end, Vals),
+ [],
+ []};
values('Grouped', Name, Mod) ->
Rname = Mod:name2rec(Name),
Rec = Mod:'#new-'(Rname),
Avps = Mod:'#info-'(Rname, fields),
- Enum = diameter_enum:combine(lists:map(fun({_,Vs,_}) -> to_enum(Vs) end,
+ Enum = diameter_enum:combine(lists:map(fun({Vs,_,_}) -> to_enum(Vs) end,
[values(F, Mod) || F <- Avps])),
- {false, diameter_enum:append(group(Mod, Name, Rec, Avps, Enum))};
+ {[],
+ diameter_enum:append(group(Mod, Name, Rec, Avps, Enum)),
+ []};
values(_, 'Framed-IP-Address', _) ->
- [{127,0,0,1}];
+ {[{127,0,0,1}],
+ [],
+ []};
values(Type, _, _) ->
values(Type).
@@ -407,12 +432,14 @@ to_enum(E) ->
%% values/2
values('AVP', _) ->
- {true, [#diameter_avp{code = 0, data = <<0>>}], []};
+ {[#diameter_avp{code = 0, data = <<0>>}],
+ [],
+ []};
values(Name, Mod) ->
Avps = types(avp_types, Mod),
{_Name, _Code, Type, _Flags} = lists:keyfind(?S(Name), 1, Avps),
- b(values(?A(Type), Name, Mod)).
+ values(?A(Type), Name, Mod).
%% group/5
%%
@@ -446,9 +473,6 @@ pack(true, Arity, Avp, Value, Acc) ->
pack(false, Arity, Avp, Value, Acc) ->
min(Arity, Avp, Value, Acc).
-all(Mod, Name, Avp, V) ->
- all(Mod:avp_arity(Name, Avp), Avp, V).
-
all(1, Avp, V) ->
{Avp, V};
all({0,'*'}, Avp, V) ->
@@ -462,9 +486,6 @@ a(N, Avp, V)
when N /= 0 ->
{Avp, lists:duplicate(N,V)}.
-min(Mod, Name, Avp, V, Acc) ->
- min(Mod:avp_arity(Name, Avp), Avp, V, Acc).
-
min(1, Avp, V, Acc) ->
[{Avp, V} | Acc];
min({0,_}, _, _, Acc) ->
diff --git a/lib/diameter/test/diameter_compiler_SUITE.erl b/lib/diameter/test/diameter_compiler_SUITE.erl
index 81722c8dca..ed369e8af3 100644
--- a/lib/diameter/test/diameter_compiler_SUITE.erl
+++ b/lib/diameter/test/diameter_compiler_SUITE.erl
@@ -31,10 +31,15 @@
%% testcases
-export([format/1, format/2,
replace/1, replace/2,
- generate/1, generate/4]).
+ generate/1, generate/4,
+ flatten1/1, flatten1/3,
+ flatten2/1]).
-export([dict/0]). %% fake dictionary module
+%% dictionary callbacks for flatten2/1
+-export(['A1'/3, 'Unsigned32'/3]).
+
-define(base, "base_rfc3588.dia").
-define(util, diameter_util).
-define(S, atom_to_list).
@@ -45,7 +50,7 @@
%% RE/Replacement (in the sense of re:replace/4) pairs for morphing
%% base_rfc3588.dia. The key is 'ok' or the the expected error as
%% returned in the first element of the error tuple returned by
-%% diameter_dict_util:parse/2.
+%% diameter_make:codec/2.
-define(REPLACE,
[{ok,
"",
@@ -335,7 +340,9 @@ suite() ->
all() ->
[format,
replace,
- generate].
+ generate,
+ flatten1,
+ flatten2].
%% Error handling testcases will make an erroneous dictionary out of
%% the base dictionary and check that the expected error results.
@@ -361,10 +368,18 @@ format(Config) ->
format(Mods, Bin) ->
B = modify(Bin, Mods),
- {ok, Dict} = diameter_dict_util:parse(B, []),
- {ok, D} = diameter_dict_util:parse(diameter_dict_util:format(Dict), []),
+ {ok, Dict} = parse(B, []),
+ {ok, D} = parse(diameter_make:format(Dict), []),
{Dict, Dict} = {Dict, D}.
+parse(File, Opts) ->
+ case diameter_make:codec(File, [parse, hrl, return | Opts]) of
+ {ok, [Dict, _]} ->
+ {ok, Dict};
+ {error, _} = E ->
+ E
+ end.
+
%% ===========================================================================
%% replace/1
%%
@@ -379,13 +394,10 @@ replace(Config) ->
replace({E, Mods}, Bin) ->
B = modify(Bin, Mods),
- case {E, diameter_dict_util:parse(B, [{include, here()}]), Mods} of
+ case {E, parse(B, [{include, here()}]), Mods} of
{ok, {ok, Dict}, _} ->
Dict;
- {_, {error, {E,_} = T}, _} ->
- S = diameter_dict_util:format_error(T),
- true = nochar($", S, E),
- true = nochar($', S, E),
+ {_, {error, S}, _} ->
S
end.
@@ -403,20 +415,127 @@ generate(Config) ->
[] = ?util:run([{?MODULE, [generate, M, Bin, N, T]}
|| {E,N} <- Rs,
{ok, M} <- [norm(E)],
- T <- [erl, hrl, spec]]).
+ T <- [erl, hrl, parse, forms]]).
generate(Mods, Bin, N, Mode) ->
B = modify(Bin, Mods ++ [{"@name .*", "@name dict" ++ ?L(N)}]),
- {ok, Dict} = diameter_dict_util:parse(B, []),
+ {ok, Dict} = parse(B, []),
File = "dict" ++ integer_to_list(N),
- {_, ok} = {Dict, diameter_codegen:from_dict("dict",
- Dict,
- [{name, File},
- {prefix, "base"},
- debug],
- Mode)},
- Mode == erl
- andalso ({ok, _} = compile:file(File ++ ".erl", [return_errors])).
+ {_, ok} = {Dict, diameter_make:codec(Dict,
+ [{name, File},
+ {prefix, "base"},
+ Mode])},
+ generate(Mode, File, Dict).
+
+generate(erl, File, _) ->
+ {ok, _} = compile:file(File ++ ".erl", [return_errors]);
+
+generate(forms, File, _) ->
+ {ok, [_]} = file:consult(File ++ ".F");
+
+generate(parse, File, Dict) ->
+ {ok, [Dict]} = file:consult(File ++ ".D"), %% assert
+ {ok, [F]} = diameter_make:codec(Dict, [forms, return]),
+ {ok, _, _, _} = compile:forms(F, [return]);
+
+generate(hrl, _, _) ->
+ ok.
+
+%% ===========================================================================
+%% flatten1/1
+
+flatten1(_Config) ->
+ [Vsn | BaseD] = diameter_gen_base_rfc6733:dict(),
+ {ok, I} = parse("@inherits diameter_gen_base_rfc6733\n", []),
+ [Vsn | FlatD] = diameter_make:flatten(I),
+ [] = ?util:run([{?MODULE, [flatten1, K, BaseD, FlatD]}
+ || K <- [avp_types, grouped, enum]]).
+
+flatten1(Key, BaseD, FlatD) ->
+ Vs = orddict:fetch(Key, BaseD),
+ Vs = orddict:fetch(Key, FlatD).
+
+%% ===========================================================================
+%% flatten2/1
+
+flatten2(_Config) ->
+ Dict1 =
+ "@name diameter_test1\n"
+ "@prefix diameter_test1\n"
+ "@vendor 666 test\n"
+ "@avp_vendor_id 111 A1 A3\n"
+ "@avp_vendor_id 222 A4 A6\n"
+ "@custom_types " ++ ?S(?MODULE) ++ " A1 A4\n"
+ "@codecs " ++ ?S(?MODULE) ++ " A3 A6\n"
+ "@avp_types\n"
+ "A1 1001 Unsigned32 V\n"
+ "A2 1002 Unsigned32 V\n"
+ "A3 1003 Unsigned32 V\n"
+ "A4 1004 Unsigned32 V\n"
+ "A5 1005 Unsigned32 V\n"
+ "A6 1006 Unsigned32 V\n"
+ "@end ignored\n",
+ Dict2 =
+ "@name diameter_test2\n"
+ "@prefix diameter_test2\n"
+ "@vendor 777 test\n"
+ "@inherits diameter_test1 A1 A2 A3\n"
+ "@inherits diameter_gen_base_rfc6733\n"
+ "@avp_vendor_id 333 A1\n",
+
+ {ok, [E1, F1]}
+ = diameter_make:codec(Dict1, [erl, forms, return]),
+ ct:pal("~s", [E1]),
+ diameter_test1 = M1 = load_forms(F1),
+
+ {ok, [D2, E2, F2]}
+ = diameter_make:codec(Dict2, [parse, erl, forms, return]),
+ ct:pal("~s", [E2]),
+ diameter_test2 = M2 = load_forms(F2),
+
+ Flat = lists:flatten(diameter_make:format(diameter_make:flatten(D2))),
+ ct:pal("~s", [Flat]),
+ {ok, [E3, F3]}
+ = diameter_make:codec(Flat, [erl, forms, return,
+ {name, "diameter_test3"}]),
+ ct:pal("~s", [E3]),
+ diameter_test3 = M3 = load_forms(F3),
+
+ [{1001, 111, M1, 'A1'}, %% @avp_vendor_id
+ {1002, 666, M1, 'A2'}, %% @vendor
+ {1003, 111, M1, 'A3'}, %% @avp_vendor_id
+ {1004, 222, M1, 'A4'}, %% @avp_vendor_id
+ {1005, 666, M1, 'A5'}, %% @vendor
+ {1006, 222, M1, 'A6'}, %% @avp_vendor_id
+ {1001, 333, M2, 'A1'}, %% M2 @avp_vendor_id
+ {1002, 666, M2, 'A2'}, %% M1 @vendor
+ {1003, 666, M2, 'A3'}, %% M1 @vendor
+ {1001, 333, M3, 'A1'}, %% (as for M2)
+ {1002, 666, M3, 'A2'}, %% "
+ {1003, 666, M3, 'A3'}] %% "
+ = [{Code, Vid, Mod, Name}
+ || Mod <- [M1, M2, M3],
+ Code <- lists:seq(1001, 1006),
+ Vid <- [666, 111, 222, 777, 333],
+ {Name, 'Unsigned32'} <- [Mod:avp_name(Code, Vid)]],
+
+ [] = [{A,T,M,RC} || A <- ['A1', 'A3'],
+ T <- [encode, decode],
+ M <- [M2, M3],
+ Ref <- [make_ref()],
+ RC <- [M:avp(T, Ref, A)],
+ RC /= {T, Ref}].
+
+'A1'(T, 'Unsigned32', Ref) ->
+ {T, Ref}.
+
+'Unsigned32'(T, 'A3', Ref) ->
+ {T, Ref}.
+
+load_forms(Forms) ->
+ {ok, Mod, Bin, _} = compile:forms(Forms, [return]),
+ {module, Mod} = code:load_binary(Mod, ?S(Mod), Bin),
+ Mod.
%% ===========================================================================
@@ -428,9 +547,6 @@ norm({E, RE, Repl}) ->
norm({_,_} = T) ->
T.
-nochar(Char, Str, Err) ->
- Err == parse orelse not lists:member(Char, Str) orelse Str.
-
here() ->
filename:dirname(code:which(?MODULE)).
diff --git a/lib/diameter/test/diameter_examples_SUITE.erl b/lib/diameter/test/diameter_examples_SUITE.erl
index 1954bc319b..02c8d34361 100644
--- a/lib/diameter/test/diameter_examples_SUITE.erl
+++ b/lib/diameter/test/diameter_examples_SUITE.erl
@@ -133,7 +133,7 @@ make(Path, Dict0) ->
try
ok = to_erl(Path, [{name, Name},
{prefix, Pre},
- {inherits, "rfc3588_base/" ++ Mod0}
+ {inherits, "common/" ++ Mod0}
| [{inherits, D ++ "/" ++ M ++ Suf}
|| {D,M} <- dep(Dict)]]),
ok = to_beam(Name)
@@ -149,7 +149,7 @@ to_erl(File, Opts) ->
No ->
throw({make, No})
end.
-
+
to_beam(Name) ->
case compile:file(Name ++ ".erl", [return]) of
{ok, _, _} ->
diff --git a/lib/diameter/test/diameter_traffic_SUITE.erl b/lib/diameter/test/diameter_traffic_SUITE.erl
index 38bdf55af8..a97c54fc04 100644
--- a/lib/diameter/test/diameter_traffic_SUITE.erl
+++ b/lib/diameter/test/diameter_traffic_SUITE.erl
@@ -171,7 +171,8 @@
{'Product-Name', "OTP/diameter"},
{'Auth-Application-Id', [?DIAMETER_APP_ID_COMMON]},
{'Acct-Application-Id', [?DIAMETER_APP_ID_ACCOUNTING]},
- {restrict_connections, false}
+ {restrict_connections, false},
+ {spawn_opt, [{min_heap_size, 5000}]}
| [{application, [{dictionary, D},
{module, ?MODULE},
{answer_errors, callback}]}
@@ -321,6 +322,7 @@ add_transports(Config) ->
LRef = ?util:listen(?SERVER,
tcp,
[{capabilities_cb, fun capx/2},
+ {spawn_opt, [{min_heap_size, 8096}]},
{applications, apps(rfc3588)}]),
Cs = [?util:connect(?CLIENT,
tcp,
diff --git a/lib/diameter/test/diameter_transport_SUITE.erl b/lib/diameter/test/diameter_transport_SUITE.erl
index 97f4cec11f..9408fae62c 100644
--- a/lib/diameter/test/diameter_transport_SUITE.erl
+++ b/lib/diameter/test/diameter_transport_SUITE.erl
@@ -180,12 +180,13 @@ reconnect({listen, Ref}) ->
[_] = diameter_reg:wait({diameter_tcp, listener, {LRef, '_'}}),
true = diameter_reg:add_new({?MODULE, Ref, LRef}),
- %% Wait for partner to request transport death: kill to force the
- %% peer to reconnect.
+ %% Wait for partner to request transport death.
TPid = abort(SvcName, LRef, Ref),
+ %% Kill transport to force the peer to reconnect.
exit(TPid, kill),
+ %% Wait for the partner again.
abort(SvcName, LRef, Ref);
reconnect({connect, Ref}) ->
@@ -200,7 +201,7 @@ reconnect({connect, Ref}) ->
%% reconnection attempts.
abort(SvcName, Pid, Ref),
- %% Transport does down and is reestablished.
+ %% Transport goes down and is reestablished.
?RECV(#diameter_event{service = SvcName, info = {down, CRef, _, _}}),
?RECV(#diameter_event{service = SvcName, info = {reconnect, CRef, _}}),
?RECV(#diameter_event{service = SvcName, info = {up, CRef, _, _, _}}),
diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl
index aa489fef5f..92c72c84e7 100644
--- a/lib/diameter/test/diameter_util.erl
+++ b/lib/diameter/test/diameter_util.erl
@@ -336,7 +336,7 @@ opts(Prot, T) ->
{transport_config, [{ip, ?ADDR}, {port, 0} | opts(T)]}].
opts(listen) ->
- [];
+ [{accept, M} || M <- [{256,0,0,1}, ["256.0.0.1", ["^.+$"]]]];
opts(PortNr) ->
[{raddr, ?ADDR}, {rport, PortNr}].