1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 2003-2019. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20
21%%
22%%----------------------------------------------------------------------
23%% Purpose: Test encoding/decoding (codec) module of Megaco/H.248
24%%----------------------------------------------------------------------
25
26-module(megaco_codec_v2_SUITE).
27
28%% ----
29
30-include_lib("megaco/include/megaco.hrl").
31-include_lib("megaco/include/megaco_message_v2.hrl").
32-include("megaco_test_lib.hrl").
33
34%% ----
35
36-export([msgs/0]).
37-export([rfc3525_msgs_display/0, rfc3525_msgs_test/0]).
38
39-export([
40 	 suite/0, all/0, groups/0,
41         init_per_suite/1, end_per_suite/1,
42         init_per_group/2, end_per_group/2,
43         init_per_testcase/2, end_per_testcase/2,
44
45	 pretty_test_msgs/1,
46
47	 compact_test_msgs/1,
48
49	 flex_pretty_init/1,
50	 flex_pretty_finish/1,
51	 flex_pretty_test_msgs/1,
52
53	 flex_compact_init/1,
54	 flex_compact_finish/1,
55	 flex_compact_test_msgs/1,
56
57	 flex_compact_dm_timers1/1,
58	 flex_compact_dm_timers2/1,
59	 flex_compact_dm_timers3/1,
60	 flex_compact_dm_timers4/1,
61	 flex_compact_dm_timers5/1,
62	 flex_compact_dm_timers6/1,
63	 flex_compact_dm_timers7/1,
64	 flex_compact_dm_timers8/1,
65
66	 bin_test_msgs/1,
67
68	 ber_test_msgs/1,
69
70	 per_test_msgs/1,
71
72	 erl_dist_m_test_msgs/1,
73
74	 compact_otp4011_msg1/1,
75	 compact_otp4011_msg2/1,
76	 compact_otp4011_msg3/1,
77	 compact_otp4013_msg1/1,
78	 compact_otp4085_msg1/1,
79	 compact_otp4085_msg2/1,
80	 compact_otp4280_msg1/1,
81	 compact_otp4299_msg1/1,
82	 compact_otp4299_msg2/1,
83	 compact_otp4359_msg1/1,
84	 compact_otp4920_msg0/1,
85	 compact_otp4920_msg1/1,
86	 compact_otp4920_msg2/1,
87	 compact_otp4920_msg3/1,
88	 compact_otp4920_msg4/1,
89	 compact_otp4920_msg5/1,
90	 compact_otp4920_msg6/1,
91	 compact_otp4920_msg7/1,
92	 compact_otp4920_msg8/1,
93	 compact_otp4920_msg9/1,
94	 compact_otp4920_msg10/1,
95	 compact_otp4920_msg11/1,
96	 compact_otp4920_msg12/1,
97	 compact_otp4920_msg20/1,
98	 compact_otp4920_msg21/1,
99	 compact_otp4920_msg22/1,
100	 compact_otp4920_msg23/1,
101	 compact_otp4920_msg24/1,
102	 compact_otp4920_msg25/1,
103	 compact_otp5186_msg01/1,
104	 compact_otp5186_msg02/1,
105	 compact_otp5186_msg03/1,
106	 compact_otp5186_msg04/1,
107	 compact_otp5186_msg05/1,
108	 compact_otp5186_msg06/1,
109	 compact_otp5290_msg01/1,
110	 compact_otp5290_msg02/1,
111	 compact_otp5793_msg01/1,
112	 compact_otp5993_msg01/1,
113	 compact_otp5993_msg02/1,
114	 compact_otp5993_msg03/1,
115         compact_otp6017_msg01/1,
116         compact_otp6017_msg02/1,
117         compact_otp6017_msg03/1,
118         compact_otp7138_msg01/1,
119         compact_otp7138_msg02/1,
120         compact_otp7457_msg01/1,
121         compact_otp7457_msg02/1,
122         compact_otp7457_msg03/1,
123	 compact_otp7534_msg01/1,
124	 compact_otp7576_msg01/1,
125         compact_otp7671_msg01/1,
126         compact_otp16818_msg01/1,
127         compact_otp16818_msg02/1,
128         compact_otp16818_msg03/1,
129         compact_otp16818_msg04/1,
130         compact_otp16818_msg05/1,
131         compact_otp16818_msg06/1,
132         compact_otp16818_msg11/1,
133         compact_otp16818_msg12/1,
134         compact_otp16818_msg13/1,
135         compact_otp16818_msg14/1,
136         compact_otp16818_msg15/1,
137         compact_otp16818_msg16/1,
138         compact_otp16818_msg21/1,
139         compact_otp16818_msg22/1,
140         compact_otp16818_msg23/1,
141         compact_otp16818_msg24/1,
142         compact_otp16818_msg25/1,
143         compact_otp16818_msg26/1,
144         compact_otp16818_msg31/1,
145         compact_otp16818_msg32/1,
146         compact_otp16818_msg33/1,
147         compact_otp16818_msg34/1,
148         compact_otp16818_msg35/1,
149         compact_otp16818_msg36/1,
150
151	 flex_compact_otp7138_msg01/1,
152	 flex_compact_otp7138_msg02/1,
153         flex_compact_otp7431_msg01/1,
154         flex_compact_otp7431_msg02/1,
155         flex_compact_otp7431_msg03/1,
156         flex_compact_otp7431_msg04/1,
157         flex_compact_otp7431_msg05/1,
158         flex_compact_otp7431_msg06/1,
159         flex_compact_otp7431_msg07/1,
160	 flex_compact_otp7457_msg01/1,
161	 flex_compact_otp7457_msg02/1,
162	 flex_compact_otp7457_msg03/1,
163         flex_compact_otp7534_msg01/1,
164         flex_compact_otp7573_msg01/1,
165	 flex_compact_otp7576_msg01/1,
166	 flex_compact_otp10998_msg01/1,
167	 flex_compact_otp10998_msg02/1,
168	 flex_compact_otp10998_msg03/1,
169	 flex_compact_otp10998_msg04/1,
170
171	 pretty_otp4632_msg1/1,
172	 pretty_otp4632_msg2/1,
173	 pretty_otp4632_msg3/1,
174	 pretty_otp4632_msg4/1,
175	 pretty_otp4710_msg1/1,
176	 pretty_otp4710_msg2/1,
177	 pretty_otp4945_msg1/1,
178	 pretty_otp4945_msg2/1,
179	 pretty_otp4945_msg3/1,
180	 pretty_otp4945_msg4/1,
181	 pretty_otp4945_msg5/1,
182	 pretty_otp4945_msg6/1,
183	 pretty_otp4949_msg1/1,
184	 pretty_otp4949_msg2/1,
185	 pretty_otp4949_msg3/1,
186	 pretty_otp5042_msg1/1,
187	 pretty_otp5068_msg1/1,
188	 pretty_otp5085_msg1/1,
189	 pretty_otp5085_msg2/1,
190	 pretty_otp5085_msg3/1,
191	 pretty_otp5085_msg4/1,
192	 pretty_otp5085_msg5/1,
193	 pretty_otp5085_msg6/1,
194	 pretty_otp5085_msg7/1,
195	 pretty_otp5600_msg1/1,
196	 pretty_otp5600_msg2/1,
197	 pretty_otp5601_msg1/1,
198         pretty_otp5793_msg01/1,
199	 pretty_otp5882_msg01/1,
200	 pretty_otp6490_msg01/1,
201	 pretty_otp6490_msg02/1,
202	 pretty_otp6490_msg03/1,
203	 pretty_otp6490_msg04/1,
204	 pretty_otp6490_msg05/1,
205	 pretty_otp6490_msg06/1,
206	 pretty_otp7249_msg01/1,
207         pretty_otp7671_msg01/1,
208         pretty_otp7671_msg02/1,
209         pretty_otp7671_msg03/1,
210         pretty_otp7671_msg04/1,
211         pretty_otp7671_msg05/1,
212
213	 flex_pretty_otp5042_msg1/1,
214	 flex_pretty_otp5085_msg1/1,
215	 flex_pretty_otp5085_msg2/1,
216	 flex_pretty_otp5085_msg3/1,
217	 flex_pretty_otp5085_msg4/1,
218	 flex_pretty_otp5085_msg5/1,
219	 flex_pretty_otp5085_msg6/1,
220	 flex_pretty_otp5085_msg7/1,
221         flex_pretty_otp5600_msg1/1,
222         flex_pretty_otp5600_msg2/1,
223         flex_pretty_otp5601_msg1/1,
224         flex_pretty_otp5793_msg01/1,
225         flex_pretty_otp7431_msg01/1,
226         flex_pretty_otp7431_msg02/1,
227         flex_pretty_otp7431_msg03/1,
228         flex_pretty_otp7431_msg04/1,
229         flex_pretty_otp7431_msg05/1,
230         flex_pretty_otp7431_msg06/1,
231         flex_pretty_otp7431_msg07/1
232	]).
233
234-export([display_text_messages/0, generate_text_messages/0]).
235
236-export([
237	 %% Decode
238	 profile_decode_compact_text_message/1,
239	 profile_decode_compact_text_messages/0,
240	 profile_decode_compact_flex_text_messages/0,
241	 profile_decode_pretty_text_message/1,
242	 profile_decode_pretty_text_messages/0,
243	 profile_decode_pretty_flex_text_messages/0,
244
245	 %% Encode
246	 profile_encode_compact_text_messages/0,
247	 profile_encode_pretty_text_messages/0
248	]).
249
250
251%% ----
252
253-define(V2,           v2).
254-define(EC,           []).
255-define(VERSION,      2).
256-define(VERSION_STR, "2").
257-define(MSG_LIB, megaco_test_msg_v2_lib).
258-define(DEFAULT_PORT, 55555).
259-define(MG1_MID_NO_PORT, {ip4Address,
260                          #'IP4Address'{address = [124, 124, 124, 222]}}).
261-define(MG1_MID, {ip4Address, #'IP4Address'{address = [124, 124, 124, 222],
262                                            portNumber = ?DEFAULT_PORT}}).
263-define(MG2_MID, {ip4Address, #'IP4Address'{address = [125, 125, 125, 111],
264                                            portNumber = ?DEFAULT_PORT}}).
265-define(MGC_MID, {ip4Address, #'IP4Address'{address = [123, 123, 123, 4],
266                                            portNumber = ?DEFAULT_PORT}}).
267
268-define(A4444, ["11111111", "00000000", "00000000"]).
269-define(A4445, ["11111111", "00000000", "11111111"]).
270-define(A5555, ["11111111", "11111111", "00000000"]).
271-define(A5556, ["11111111", "11111111", "11111111"]).
272
273
274%%======================================================================
275%% Common Test interface functions
276%%======================================================================
277
278suite() ->
279    [{ct_hooks, [ts_install_cth]}].
280
281all() ->
282    [
283     {group, text},
284     {group, binary},
285     {group, erl_dist},
286     {group, tickets}
287    ].
288
289groups() ->
290    [
291     {text,                 [], text_cases()},
292     {binary,               [], binary_cases()},
293     {erl_dist,             [], erl_dist_cases()},
294     {pretty,               [], pretty_cases()},
295     {compact,              [], compact_cases()},
296     {flex_pretty,          [], flex_pretty_cases()},
297     {flex_compact,         [], flex_compact_cases()},
298     {bin,                  [], bin_cases()},
299     {ber,                  [], ber_cases()},
300     {per,                  [], per_cases()},
301     {erl_dist_m,           [], erl_dist_m_cases()},
302     {tickets,              [], tickets_cases()},
303     {compact_tickets,      [], compact_tickets_cases()},
304     {flex_compact_tickets, [], flex_compact_tickets_cases()},
305     {pretty_tickets,       [], pretty_tickets_cases()},
306     {flex_pretty_tickets,  [], flex_pretty_tickets_cases()}
307    ].
308
309
310text_cases() ->
311    [
312     {group, pretty},
313     {group, flex_pretty},
314     {group, compact},
315     {group, flex_compact}
316    ].
317
318binary_cases() ->
319    [
320     {group, bin},
321     {group, ber},
322     {group, per}
323    ].
324
325erl_dist_cases() ->
326    [
327     {group, erl_dist_m}
328    ].
329
330pretty_cases() ->
331    [
332     pretty_test_msgs
333    ].
334
335compact_cases() ->
336    [
337     compact_test_msgs
338    ].
339
340flex_pretty_cases() ->
341    [
342     flex_pretty_test_msgs
343    ].
344
345flex_compact_cases() ->
346    [
347     flex_compact_test_msgs,
348     flex_compact_dm_timers1,
349     flex_compact_dm_timers2,
350     flex_compact_dm_timers3,
351     flex_compact_dm_timers4,
352     flex_compact_dm_timers5,
353     flex_compact_dm_timers6,
354     flex_compact_dm_timers7,
355     flex_compact_dm_timers8
356    ].
357
358bin_cases() ->
359    [
360     bin_test_msgs
361    ].
362
363ber_cases() ->
364    [
365     ber_test_msgs
366    ].
367
368per_cases() ->
369    [
370     per_test_msgs
371    ].
372
373erl_dist_m_cases() ->
374    [
375     erl_dist_m_test_msgs
376    ].
377
378tickets_cases() ->
379    [
380     {group, compact_tickets},
381     {group, pretty_tickets},
382     {group, flex_compact_tickets},
383     {group, flex_pretty_tickets}
384    ].
385
386compact_tickets_cases() ->
387    [
388     compact_otp4011_msg1,
389     compact_otp4011_msg2,
390     compact_otp4011_msg3,
391     compact_otp4013_msg1,
392
393     compact_otp4085_msg1,
394     compact_otp4085_msg2,
395
396     compact_otp4280_msg1,
397
398     compact_otp4299_msg1,
399     compact_otp4299_msg2,
400
401     compact_otp4359_msg1,
402
403     compact_otp4920_msg0,
404     compact_otp4920_msg1,
405     compact_otp4920_msg2,
406     compact_otp4920_msg3,
407     compact_otp4920_msg4,
408     compact_otp4920_msg5,
409     compact_otp4920_msg6,
410     compact_otp4920_msg7,
411     compact_otp4920_msg8,
412     compact_otp4920_msg9,
413     compact_otp4920_msg10,
414     compact_otp4920_msg11,
415     compact_otp4920_msg12,
416     compact_otp4920_msg20,
417     compact_otp4920_msg21,
418     compact_otp4920_msg22,
419     compact_otp4920_msg23,
420     compact_otp4920_msg24,
421     compact_otp4920_msg25,
422
423     compact_otp5186_msg01,
424     compact_otp5186_msg02,
425     compact_otp5186_msg03,
426     compact_otp5186_msg04,
427     compact_otp5186_msg05,
428     compact_otp5186_msg06,
429
430     compact_otp5290_msg01,
431     compact_otp5290_msg02,
432
433     compact_otp5793_msg01,
434
435     compact_otp5993_msg01,
436     compact_otp5993_msg02,
437     compact_otp5993_msg03,
438
439     compact_otp6017_msg01,
440     compact_otp6017_msg02,
441     compact_otp6017_msg03,
442
443     compact_otp7138_msg01,
444     compact_otp7138_msg02,
445
446     compact_otp7457_msg01,
447     compact_otp7457_msg02,
448     compact_otp7457_msg03,
449
450     compact_otp7534_msg01,
451
452     compact_otp7576_msg01,
453
454     compact_otp7671_msg01,
455
456     compact_otp16818_msg01,
457     compact_otp16818_msg02,
458     compact_otp16818_msg03,
459     compact_otp16818_msg04,
460     compact_otp16818_msg05,
461     compact_otp16818_msg06,
462     compact_otp16818_msg11,
463     compact_otp16818_msg12,
464     compact_otp16818_msg13,
465     compact_otp16818_msg14,
466     compact_otp16818_msg15,
467     compact_otp16818_msg16,
468     compact_otp16818_msg21,
469     compact_otp16818_msg22,
470     compact_otp16818_msg23,
471     compact_otp16818_msg24,
472     compact_otp16818_msg25,
473     compact_otp16818_msg26,
474     compact_otp16818_msg31,
475     compact_otp16818_msg32,
476     compact_otp16818_msg33,
477     compact_otp16818_msg34,
478     compact_otp16818_msg35,
479     compact_otp16818_msg36
480    ].
481
482flex_compact_tickets_cases() ->
483    [
484     flex_compact_otp7138_msg01,
485     flex_compact_otp7138_msg02,
486     flex_compact_otp7431_msg01,
487     flex_compact_otp7431_msg02,
488     flex_compact_otp7431_msg03,
489     flex_compact_otp7431_msg04,
490     flex_compact_otp7431_msg05,
491     flex_compact_otp7431_msg06,
492     flex_compact_otp7431_msg07,
493     flex_compact_otp7138_msg02,
494     flex_compact_otp7457_msg01,
495     flex_compact_otp7457_msg02,
496     flex_compact_otp7457_msg03,
497     flex_compact_otp7534_msg01,
498     flex_compact_otp7573_msg01,
499     flex_compact_otp7576_msg01,
500     flex_compact_otp10998_msg01,
501     flex_compact_otp10998_msg02,
502     flex_compact_otp10998_msg03,
503     flex_compact_otp10998_msg04
504    ].
505
506pretty_tickets_cases() ->
507    [
508     pretty_otp4632_msg1,
509     pretty_otp4632_msg2,
510     pretty_otp4632_msg3,
511     pretty_otp4632_msg4,
512
513     pretty_otp4710_msg1,
514     pretty_otp4710_msg2,
515
516     pretty_otp4945_msg1,
517     pretty_otp4945_msg2,
518     pretty_otp4945_msg3,
519     pretty_otp4945_msg4,
520     pretty_otp4945_msg5,
521     pretty_otp4945_msg6,
522
523     pretty_otp4949_msg1,
524     pretty_otp4949_msg2,
525     pretty_otp4949_msg3,
526
527     pretty_otp5042_msg1,
528
529     pretty_otp5068_msg1,
530
531     pretty_otp5085_msg1,
532     pretty_otp5085_msg2,
533     pretty_otp5085_msg3,
534     pretty_otp5085_msg4,
535     pretty_otp5085_msg5,
536     pretty_otp5085_msg6,
537     pretty_otp5085_msg7,
538
539     pretty_otp5600_msg1,
540     pretty_otp5600_msg2,
541
542     pretty_otp5601_msg1,
543
544     pretty_otp5793_msg01,
545
546     pretty_otp5882_msg01,
547
548     pretty_otp6490_msg01,
549     pretty_otp6490_msg02,
550     pretty_otp6490_msg03,
551     pretty_otp6490_msg04,
552     pretty_otp6490_msg05,
553     pretty_otp6490_msg06,
554
555     pretty_otp7249_msg01,
556
557     pretty_otp7671_msg01,
558     pretty_otp7671_msg02,
559     pretty_otp7671_msg03,
560     pretty_otp7671_msg04,
561     pretty_otp7671_msg05
562    ].
563
564
565flex_pretty_tickets_cases() ->
566    [
567     flex_pretty_otp5042_msg1,
568     flex_pretty_otp5085_msg1,
569     flex_pretty_otp5085_msg2,
570     flex_pretty_otp5085_msg3,
571     flex_pretty_otp5085_msg4,
572     flex_pretty_otp5085_msg5,
573     flex_pretty_otp5085_msg6,
574     flex_pretty_otp5085_msg7,
575     flex_pretty_otp5600_msg1,
576     flex_pretty_otp5600_msg2,
577     flex_pretty_otp5601_msg1,
578     flex_pretty_otp5793_msg01,
579     flex_pretty_otp7431_msg01,
580     flex_pretty_otp7431_msg02,
581     flex_pretty_otp7431_msg03,
582     flex_pretty_otp7431_msg04,
583     flex_pretty_otp7431_msg05,
584     flex_pretty_otp7431_msg06,
585     flex_pretty_otp7431_msg07
586    ].
587
588
589
590%%
591%% -----
592%%
593
594init_per_suite(suite) ->
595    [];
596init_per_suite(doc) ->
597    [];
598init_per_suite(Config0) when is_list(Config0) ->
599
600    ?ANNOUNCE_SUITE_INIT(),
601
602    p("init_per_suite -> entry with"
603      "~n      Config: ~p"
604      "~n      Nodes:  ~p", [Config0, erlang:nodes()]),
605
606    case ?LIB:init_per_suite(Config0) of
607        {skip, _} = SKIP ->
608            SKIP;
609
610        Config1 when is_list(Config1) ->
611
612            %% We need a (local) monitor on this node also
613            megaco_test_sys_monitor:start(),
614
615            p("init_per_suite -> end when"
616              "~n      Config: ~p"
617              "~n      Nodes:  ~p", [Config1, erlang:nodes()]),
618
619            Config1
620    end.
621
622end_per_suite(suite) -> [];
623end_per_suite(doc) -> [];
624end_per_suite(Config0) when is_list(Config0) ->
625
626    p("end_per_suite -> entry with"
627      "~n      Config: ~p"
628      "~n      Nodes:  ~p", [Config0, erlang:nodes()]),
629
630    megaco_test_sys_monitor:stop(),
631    Config1 = ?LIB:end_per_suite(Config0),
632
633    p("end_per_suite -> end when"
634      "~n      Nodes:  ~p", [erlang:nodes()]),
635
636    Config1.
637
638
639%%
640%% -----
641%%
642
643init_per_group(flex_pretty_tickets = Group, Config) ->
644    ?ANNOUNCE_GROUP_INIT(Group),
645    flex_pretty_init(Config);
646init_per_group(flex_compact_tickets = Group, Config) ->
647    ?ANNOUNCE_GROUP_INIT(Group),
648    flex_compact_init(Config);
649init_per_group(flex_compact = Group, Config) ->
650    ?ANNOUNCE_GROUP_INIT(Group),
651    flex_compact_init(Config);
652init_per_group(flex_pretty = Group, Config) ->
653    ?ANNOUNCE_GROUP_INIT(Group),
654    flex_pretty_init(Config);
655init_per_group(Group, Config) ->
656    ?ANNOUNCE_GROUP_INIT(Group),
657    Config.
658
659end_per_group(flex_pretty_tickets = _Group, Config) ->
660    flex_pretty_finish(Config);
661end_per_group(flex_compact_tickets = _Group, Config) ->
662    flex_compact_finish(Config);
663end_per_group(flex_compact = _Group, Config) ->
664    flex_compact_finish(Config);
665end_per_group(flex_pretty = _Group, Config) ->
666    flex_pretty_finish(Config);
667end_per_group(_Group, Config) ->
668    Config.
669
670
671
672%%
673%% -----
674%%
675
676init_per_testcase(Case, Config) ->
677    %% We do *not* reset events with each test case
678    %% The test cases are so short we don't bother,
679    %% and also we would drown in mprintouts...
680    put(verbosity,trc),
681    megaco_test_lib:init_per_testcase(Case, Config).
682
683end_per_testcase(Case, Config) ->
684    erase(verbosity),
685    megaco_test_lib:end_per_testcase(Case, Config).
686
687
688
689
690%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
691
692display_text_messages() ->
693    Msgs =
694        msgs4() ++
695	msgs5(),
696    megaco_codec_test_lib:display_text_messages(?VERSION, Msgs).
697
698
699%% ----
700
701generate_text_messages() ->
702    Msgs =
703        msgs4() ++
704	msgs5(),
705    megaco_codec_test_lib:generate_text_messages(?V2, ?VERSION, ?EC, Msgs).
706
707
708%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
709
710%% (catch megaco_codec_v2_test:profile_decode_compact_text_message(msg51a)).
711%% (catch megaco_codec_v2_test:profile_decode_compact_text_message(msg51b)).
712%% (catch megaco_codec_v2_test:profile_decode_compact_text_message(msg52)).
713%% (catch megaco_codec_v2_test:profile_decode_compact_text_message(msg53)).
714%% (catch megaco_codec_v2_test:profile_decode_compact_text_message(msg54a)).
715%% (catch megaco_codec_v2_test:profile_decode_compact_text_message(msg58a)).
716%% (catch megaco_codec_v2_test:profile_decode_compact_text_message(msg58b)).
717%% (catch megaco_codec_v2_test:profile_decode_compact_text_message(msg61a)).
718profile_decode_compact_text_message(MsgTag) ->
719    Codec  = megaco_compact_text_encoder,
720    Config = [],
721    profile_decode_text_message(Codec, Config, MsgTag).
722
723%% (catch megaco_codec_v2_test:profile_decode_pretty_text_message(msg51a)).
724%% (catch megaco_codec_v2_test:profile_decode_pretty_text_message(msg51b)).
725%% (catch megaco_codec_v2_test:profile_decode_pretty_text_message(msg52)).
726profile_decode_pretty_text_message(MsgTag) ->
727    Codec  = megaco_pretty_text_encoder,
728    Config = [],
729    profile_decode_text_message(Codec, Config, MsgTag).
730
731profile_decode_text_message(Codec, Config, MsgTag) ->
732    Msgs = msgs4() ++ msgs5(),
733    case lists:keysearch(MsgTag, 1, Msgs) of
734	{value, Msg} ->
735	    profile_decode_text_messages(Codec, Config, [Msg]);
736	false ->
737	    {error, {no_such_message, MsgTag}}
738    end.
739
740
741%% (catch megaco_codec_v2_test:profile_decode_compact_text_messages()).
742profile_decode_compact_text_messages() ->
743    Config = [],
744    Slogan = decode_compact_v2,
745    profile_decode_compact_text_messages(Slogan, Config).
746
747%% (catch megaco_codec_v2_test:profile_decode_compact_flex_text_messages()).
748profile_decode_compact_flex_text_messages() ->
749    Conf   = flex_init([]),
750    Config = flex_scanner_conf(Conf),
751    Slogan = decode_compact_flex_v2,
752    Res = profile_decode_compact_text_messages(Slogan, [Config]),
753    flex_finish(Conf),
754    Res.
755
756profile_decode_compact_text_messages(Slogan, Config) ->
757    Codec = megaco_compact_text_encoder,
758    profile_decode_text_messages(Slogan, Codec, Config).
759
760%% (catch megaco_codec_v2_test:profile_decode_pretty_text_messages()).
761profile_decode_pretty_text_messages() ->
762    Config = [],
763    Slogan = decode_pretty_v2,
764    profile_decode_pretty_text_messages(Slogan, Config).
765
766%% (catch megaco_codec_v2_test:profile_decode_pretty_flex_text_messages()).
767profile_decode_pretty_flex_text_messages() ->
768    Conf   = flex_init([]),
769    Config = flex_scanner_conf(Conf),
770    Slogan = decode_pretty_flex_v2,
771    Res    = profile_decode_pretty_text_messages(Slogan, [Config]),
772    flex_finish(Conf),
773    Res.
774
775profile_decode_pretty_text_messages(Slogan, Config) ->
776    Codec = megaco_pretty_text_encoder,
777    profile_decode_text_messages(Slogan, Codec, Config).
778
779profile_decode_text_messages(Slogan, Codec, Config) ->
780    Msgs = msgs4() ++ msgs5(),
781    profile_decode_text_messages(Slogan, Codec, Config, Msgs).
782
783profile_decode_text_messages(Slogan, Codec, Config, Msgs0) ->
784    Msgs      = [Msg || {_, Msg, _, _} <- Msgs0],
785    EncodeRes = encode_text_messages(Codec, Config, Msgs, []),
786    Bins      = [Bin || {ok, Bin} <- EncodeRes],
787    Fun = fun() ->
788		  decode_text_messages(Codec, Config, Bins, [])
789	  end,
790    %% Make a dry run, just to make sure all modules are loaded:
791    io:format("make a dry run...~n", []),
792    (catch Fun()),
793    io:format("make the run...~n", []),
794    megaco_profile:profile(Slogan, Fun).
795
796%% (catch megaco_codec_v2_test:profile_encode_compact_text_messages()).
797profile_encode_compact_text_messages() ->
798    Codec  = megaco_compact_text_encoder,
799    Config = [],
800    Slogan = encode_compact_v2,
801    profile_encode_text_messages(Slogan, Codec, Config).
802
803%% (catch megaco_codec_v2_test:profile_encode_pretty_text_messages()).
804profile_encode_pretty_text_messages() ->
805    Codec  = megaco_pretty_text_encoder,
806    Config = [],
807    Slogan = encode_pretty_v2,
808    profile_encode_text_messages(Slogan, Codec, Config).
809
810profile_encode_text_messages(Slogan, Codec, Config) ->
811    Msgs = msgs4() ++ msgs5(),
812    profile_encode_text_messages(Slogan, Codec, Config, Msgs).
813
814profile_encode_text_messages(Slogan, Codec, Config, Msgs0) ->
815    Msgs = [Msg || {_, Msg, _, _} <- Msgs0],
816    Fun = fun() ->
817		  encode_text_messages(Codec, Config, Msgs, [])
818	  end,
819    %% Make a dry run, just to make sure all modules are loaded:
820    io:format("make a dry run...~n", []),
821    (catch Fun()),
822    io:format("make the run...~n", []),
823    megaco_profile:profile(Slogan, Fun).
824
825encode_text_messages(_Codec, _Config, [], Acc) ->
826    Acc;
827encode_text_messages(Codec, Config, [Msg|Msgs], Acc) ->
828    Res = Codec:encode_message(Config, ?VERSION, Msg),
829    encode_text_messages(Codec, Config, Msgs, [Res | Acc]).
830
831decode_text_messages(_Codec, _Config, [], Acc) ->
832    Acc;
833decode_text_messages(Codec, Config, [Msg|Msgs], Acc) ->
834    Res = Codec:decode_message(Config, dynamic, Msg),
835    decode_text_messages(Codec, Config, Msgs, [Res | Acc]).
836
837
838%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
839
840pretty_test_msgs(suite) ->
841    [];
842pretty_test_msgs(Config) when is_list(Config) ->
843    ?ACQUIRE_NODES(1, Config),
844    Msgs = msgs1() ++ msgs2() ++ msgs3() ++ msgs4() ++ msgs5(),
845    %% Msgs = msgs5(),
846    DynamicDecode = false,
847    test_msgs(megaco_pretty_text_encoder, DynamicDecode, [], Msgs).
848
849
850%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
851
852flex_pretty_init(Config) ->
853        flex_init(Config).
854
855flex_pretty_finish(Config) ->
856    flex_finish(Config).
857
858
859flex_pretty_test_msgs(suite) ->
860    [];
861flex_pretty_test_msgs(Config) when is_list(Config) ->
862    ?ACQUIRE_NODES(1, Config),
863    Msgs = msgs1() ++ msgs2() ++ msgs3() ++ msgs4(),
864    Conf = flex_scanner_conf(Config),
865    DynamicDecode = false,
866    test_msgs(megaco_pretty_text_encoder, DynamicDecode, [Conf], Msgs).
867
868
869flex_pretty_otp5042_msg1(suite) ->
870    [];
871flex_pretty_otp5042_msg1(Config) when is_list(Config) ->
872    d("flex_pretty_otp5042_msg1 -> entry", []),
873    ?ACQUIRE_NODES(1, Config),
874    Msg0 = pretty_otp5042_msg1(),
875    Bin0 = list_to_binary(Msg0),
876    Conf = flex_scanner_conf(Config),
877    case decode_message(megaco_pretty_text_encoder, false, [Conf], Bin0) of
878	{error, [{reason, Reason}|_]} ->
879	    case Reason of
880		{_, _Mod, {bad_timeStamp, TimeStamp}} ->
881		    exit({bad_timeStamp, TimeStamp});
882		_ ->
883		    io:format("flex_pretty_otp5042_msg1 -> "
884			      "~n   Reason: ~w"
885			      "~n", [Reason]),
886		    exit({unexpected_decode_result, Reason})
887	    end;
888	{ok, M} ->
889	    t("flex_pretty_otp5042_msg1 -> successfull decode:"
890	      "~n~p", [M]),
891	    ok
892    end.
893
894
895flex_pretty_otp5085_msg1(suite) ->
896    [];
897flex_pretty_otp5085_msg1(Config) when is_list(Config) ->
898    d("flex_pretty_otp5085_msg1 -> entry", []),
899    ?ACQUIRE_NODES(1, Config),
900    Conf = flex_scanner_conf(Config),
901    pretty_otp5085(ok, pretty_otp5085_msg1(), [Conf]).
902
903flex_pretty_otp5085_msg2(suite) ->
904    [];
905flex_pretty_otp5085_msg2(Config) when is_list(Config) ->
906    d("flex_pretty_otp5085_msg2 -> entry", []),
907    ?ACQUIRE_NODES(1, Config),
908    Conf = flex_scanner_conf(Config),
909    pretty_otp5085(error, pretty_otp5085_msg2(), [Conf]).
910
911flex_pretty_otp5085_msg3(suite) ->
912    [];
913flex_pretty_otp5085_msg3(Config) when is_list(Config) ->
914    d("flex_pretty_otp5085_msg3 -> entry", []),
915    ?ACQUIRE_NODES(1, Config),
916    Conf = flex_scanner_conf(Config),
917    pretty_otp5085(ok, pretty_otp5085_msg3(), [Conf]).
918
919flex_pretty_otp5085_msg4(suite) ->
920    [];
921flex_pretty_otp5085_msg4(Config) when is_list(Config) ->
922    d("flex_pretty_otp5085_msg4 -> entry", []),
923    ?ACQUIRE_NODES(1, Config),
924    Conf = flex_scanner_conf(Config),
925    pretty_otp5085(ok, pretty_otp5085_msg4(), [Conf]).
926
927flex_pretty_otp5085_msg5(suite) ->
928    [];
929flex_pretty_otp5085_msg5(Config) when is_list(Config) ->
930    d("flex_pretty_otp5085_msg5 -> entry", []),
931    ?ACQUIRE_NODES(1, Config),
932    Conf = flex_scanner_conf(Config),
933    pretty_otp5085(ok, pretty_otp5085_msg5(), [Conf]).
934
935flex_pretty_otp5085_msg6(suite) ->
936    [];
937flex_pretty_otp5085_msg6(Config) when is_list(Config) ->
938    d("flex_pretty_otp5085_msg6 -> entry", []),
939    ?ACQUIRE_NODES(1, Config),
940    Conf = flex_scanner_conf(Config),
941    pretty_otp5085(ok, pretty_otp5085_msg6(), [Conf]).
942
943flex_pretty_otp5085_msg7(suite) ->
944    [];
945flex_pretty_otp5085_msg7(Config) when is_list(Config) ->
946    d("flex_pretty_otp5085_msg7 -> entry", []),
947    ?ACQUIRE_NODES(1, Config),
948    Conf = flex_scanner_conf(Config),
949    pretty_otp5085(ok, pretty_otp5085_msg7(), [Conf]).
950
951flex_pretty_otp5600_msg1(suite) ->
952    [];
953flex_pretty_otp5600_msg1(Config) when is_list(Config) ->
954    d("flex_pretty_otp5600_msg1 -> entry", []),
955    ?ACQUIRE_NODES(1, Config),
956    Conf = flex_scanner_conf(Config),
957    pretty_otp5600(ok, pretty_otp5600_msg1(), [Conf]).
958
959flex_pretty_otp5600_msg2(suite) ->
960    [];
961flex_pretty_otp5600_msg2(Config) when is_list(Config) ->
962    d("flex_pretty_otp5600_msg2 -> entry", []),
963    ?ACQUIRE_NODES(1, Config),
964    Conf = flex_scanner_conf(Config),
965    pretty_otp5600(ok, pretty_otp5600_msg2(), [Conf]).
966
967flex_pretty_otp5601_msg1(suite) ->
968    [];
969flex_pretty_otp5601_msg1(Config) when is_list(Config) ->
970    d("flex_pretty_otp5601_msg1 -> entry", []),
971    ?ACQUIRE_NODES(1, Config),
972    Conf = flex_scanner_conf(Config),
973    pretty_otp5601(ok, pretty_otp5601_msg1(), [Conf]).
974
975flex_pretty_otp5793_msg01(suite) ->
976    [];
977flex_pretty_otp5793_msg01(Config) when is_list(Config) ->
978    d("flex_pretty_otp5793_msg01 -> entry", []),
979    ?ACQUIRE_NODES(1, Config),
980    Conf = flex_scanner_conf(Config),
981    pretty_otp5793(ok, pretty_otp5793_msg1(), [Conf]).
982
983
984flex_pretty_otp7431_msg01(suite) ->
985    [];
986flex_pretty_otp7431_msg01(Config) when is_list(Config) ->
987    d("flex_pretty_otp7431_msg01 -> entry", []),
988    ?ACQUIRE_NODES(1, Config),
989    Conf = flex_scanner_conf(Config),
990    flex_pretty_otp7431(ok, flex_pretty_otp7431_msg1(), [Conf]).
991
992flex_pretty_otp7431_msg02(suite) ->
993    [];
994flex_pretty_otp7431_msg02(Config) when is_list(Config) ->
995    %%     put(severity,trc),
996    %%     put(dbg,true),
997    d("flex_pretty_otp7431_msg02 -> entry", []),
998    ?ACQUIRE_NODES(1, Config),
999    Conf = flex_scanner_conf(Config),
1000    flex_pretty_otp7431(error, flex_pretty_otp7431_msg2(), [Conf]).
1001
1002flex_pretty_otp7431_msg03(suite) ->
1003    [];
1004flex_pretty_otp7431_msg03(Config) when is_list(Config) ->
1005    %%     put(severity,trc),
1006    %%     put(dbg,true),
1007    d("flex_pretty_otp7431_msg03 -> entry", []),
1008    ?ACQUIRE_NODES(1, Config),
1009    Conf = flex_scanner_conf(Config),
1010    flex_pretty_otp7431(error, flex_pretty_otp7431_msg3(), [Conf]).
1011
1012flex_pretty_otp7431_msg04(suite) ->
1013    [];
1014flex_pretty_otp7431_msg04(Config) when is_list(Config) ->
1015    d("flex_pretty_otp7431_msg04 -> entry", []),
1016    ?ACQUIRE_NODES(1, Config),
1017    Conf = flex_scanner_conf(Config),
1018    flex_pretty_otp7431(error, flex_pretty_otp7431_msg4(), [Conf]).
1019
1020flex_pretty_otp7431_msg05(suite) ->
1021    [];
1022flex_pretty_otp7431_msg05(Config) when is_list(Config) ->
1023    d("flex_pretty_otp7431_msg05 -> entry", []),
1024    ?ACQUIRE_NODES(1, Config),
1025    Conf = flex_scanner_conf(Config),
1026    flex_pretty_otp7431(error, flex_pretty_otp7431_msg5(), [Conf]).
1027
1028flex_pretty_otp7431_msg06(suite) ->
1029    [];
1030flex_pretty_otp7431_msg06(Config) when is_list(Config) ->
1031    d("flex_pretty_otp7431_msg06 -> entry", []),
1032    ?ACQUIRE_NODES(1, Config),
1033    Conf = flex_scanner_conf(Config),
1034    flex_pretty_otp7431(error, flex_pretty_otp7431_msg6(), [Conf]).
1035
1036flex_pretty_otp7431_msg07(suite) ->
1037    [];
1038flex_pretty_otp7431_msg07(Config) when is_list(Config) ->
1039    d("flex_pretty_otp7431_msg07 -> entry", []),
1040    ?ACQUIRE_NODES(1, Config),
1041    Conf = flex_scanner_conf(Config),
1042    flex_pretty_otp7431(error, flex_pretty_otp7431_msg7(), [Conf]).
1043
1044flex_pretty_otp7431(Expected, Msg, Conf) ->
1045    otp7431(Expected, megaco_pretty_text_encoder, Msg, Conf).
1046
1047otp7431(Expected, Codec, Msg0, Conf) ->
1048    Bin0 = list_to_binary(Msg0),
1049    case decode_message(Codec, false, Conf, Bin0) of
1050	{ok, _Msg1} when Expected =:= ok ->
1051 	    io:format(" decoded", []);
1052	{error, {bad_property_parm, Reason}} when (Expected =:= error) andalso
1053						  is_list(Reason) ->
1054	    io:format("expected result: ~s", [Reason]),
1055	    ok;
1056	Else ->
1057	    io:format("unexpected result", []),
1058	    exit({unexpected_decode_result, Else})
1059    end.
1060
1061
1062flex_pretty_otp7431_msg1() ->
1063    "MEGACO/" ?VERSION_STR " [124.124.124.222]:55555 Reply = 10003 {
1064   Context = 2000 {
1065	       Add = A4444,
1066	       Add = A4445 {
1067		       Media {
1068			 Stream = 1 {
1069				    Local {
1070				      v=0
1071				      o=- 2890844526 2890842807 IN IP4 124.124.124.222
1072				      s=-
1073				      t= 0 0
1074				      c=IN IP4 124.124.124.222
1075				      m=audio 2222 RTP/AVP 4
1076				      a=ptime:30
1077				      a=recvonly
1078				     } ; RTP profile for G.723.1 is 4
1079				   }
1080			}
1081		      }
1082	      }
1083       }".
1084
1085flex_pretty_otp7431_msg2() ->
1086    "MEGACO/" ?VERSION_STR " [124.124.124.222]:55555 Reply = 10003 {
1087   Context = 2000 {
1088	       Add = A4444,
1089	       Add = A4445 {
1090		       Media {
1091			 Stream = 1 {
1092				    Local {
1093				      v=0
1094				      o=- 2890844526 2890842807 IN IP4 124.124.124.222
1095				      s=-
1096				      t= 0 0
1097				      c=IN IP4 124.124.124.222
1098				      m=audio 2222 RTP/AVP 4
1099				      a=ptime:30
1100				      a=             }
1101				   }
1102			}
1103		      }
1104	      }
1105       }".
1106
1107flex_pretty_otp7431_msg3() ->
1108    "MEGACO/" ?VERSION_STR " [124.124.124.222]:55555 Reply = 10003 {
1109   Context = 2000 {
1110	       Add = A4444,
1111	       Add = A4445 {
1112		       Media {
1113			 Stream = 1 {
1114				    Local {
1115				      v=0
1116				      o=- 2890844526 2890842807 IN IP4 124.124.124.222
1117				      s=-
1118				      t= 0 0
1119				      c=IN IP4 124.124.124.222
1120				      m=audio 2222 RTP/AVP 4
1121				      a=ptime:30
1122				      a             }
1123				   }
1124			}
1125		      }
1126	      }
1127       }".
1128
1129flex_pretty_otp7431_msg4() ->
1130    "MEGACO/" ?VERSION_STR " [124.124.124.222]:55555 Reply = 10003 {
1131   Context = 2000 {
1132	       Add = A4444,
1133	       Add = A4445 {
1134		       Media {
1135			 Stream = 1 {
1136				    Local {
1137				      v=0
1138				      o=- 2890844526 2890842807 IN IP4 124.124.124.222
1139				      s=-
1140				      t= 0 0
1141				      c=IN IP4 124.124.124.222
1142				      m=audio 2222 RTP/AVP 4
1143				      a=ptime:30
1144				      a}
1145				   }
1146			}
1147		      }
1148	      }
1149       }".
1150
1151flex_pretty_otp7431_msg5() ->
1152    "MEGACO/" ?VERSION_STR " [124.124.124.222]:55555 Reply = 10003 {
1153   Context = 2000 {
1154	       Add = A4444,
1155	       Add = A4445 {
1156		       Media {
1157			 Stream = 1 {
1158				    Local {
1159				      v=            }
1160				   }
1161			}
1162		      }
1163	      }
1164       }".
1165
1166flex_pretty_otp7431_msg6() ->
1167    "MEGACO/" ?VERSION_STR " [124.124.124.222]:55555 Reply = 10003 {
1168   Context = 2000 {
1169	       Add = A4444,
1170	       Add = A4445 {
1171		       Media {
1172			 Stream = 1 {
1173				    Local {
1174				      v            }
1175				   }
1176			}
1177		      }
1178	      }
1179       }".
1180
1181flex_pretty_otp7431_msg7() ->
1182    "MEGACO/" ?VERSION_STR " [124.124.124.222]:55555 Reply = 10003 {
1183   Context = 2000 {
1184	       Add = A4444,
1185	       Add = A4445 {
1186		       Media {
1187			 Stream = 1 {
1188				    Local {
1189				      v}
1190				   }
1191			}
1192		      }
1193	      }
1194       }".
1195
1196
1197
1198%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1199
1200compact_test_msgs(suite) ->
1201    [];
1202compact_test_msgs(Config) when is_list(Config) ->
1203    ?ACQUIRE_NODES(1, Config),
1204    Msgs = msgs1() ++ msgs2() ++ msgs3() ++ msgs4(),
1205    DynamicDecode = false,
1206    test_msgs(megaco_compact_text_encoder, DynamicDecode, [], Msgs).
1207
1208
1209%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1210
1211flex_compact_init(Config) ->
1212    flex_init(Config).
1213
1214flex_compact_finish(Config) ->
1215    flex_finish(Config).
1216
1217
1218flex_compact_test_msgs(suite) ->
1219    [];
1220flex_compact_test_msgs(Config) when is_list(Config) ->
1221    ?ACQUIRE_NODES(1, Config),
1222    Msgs = msgs1() ++ msgs2() ++ msgs3() ++ msgs4(),
1223    Conf = flex_scanner_conf(Config),
1224    DynamicDecode = true,
1225    test_msgs(megaco_compact_text_encoder, DynamicDecode, [Conf], Msgs).
1226
1227
1228flex_compact_dm_timers1(suite) ->
1229    [];
1230flex_compact_dm_timers1(Config) when is_list(Config) ->
1231    ?ACQUIRE_NODES(1, Config),
1232    M = build_dm_timers_message("1", "2", "3"),
1233    B = list_to_binary(M),
1234    Conf = flex_scanner_conf(Config),
1235    case decode_message(megaco_compact_text_encoder, false, [Conf], B) of
1236	{ok, M1} when is_record(M1,'MegacoMessage') ->
1237	    t("flex_compact_dm_timers1 -> "
1238	      "~n   M:  ~s"
1239	      "~n   M1: ~p", [M, M1]),
1240	    verify_dm_timers({1,2,3}, M1);
1241	Else ->
1242	    exit({decode_failed, M, Else})
1243    end.
1244
1245
1246flex_compact_dm_timers2(suite) ->
1247    [];
1248flex_compact_dm_timers2(Config) when is_list(Config) ->
1249    ?ACQUIRE_NODES(1, Config),
1250    M = build_dm_timers_message("02", "03", "04"),
1251    B = list_to_binary(M),
1252    Conf = flex_scanner_conf(Config),
1253    case decode_message(megaco_compact_text_encoder, false, [Conf], B) of
1254	{ok, M1} when is_record(M1,'MegacoMessage') ->
1255	    t("flex_compact_dm_timers2 -> "
1256	      "~n   M:  ~s"
1257	      "~n   M1: ~p", [M, M1]),
1258	    verify_dm_timers({2,3,4}, M1);
1259	Else ->
1260	    exit({decode_failed, M, Else})
1261    end.
1262
1263
1264flex_compact_dm_timers3(suite) ->
1265    [];
1266flex_compact_dm_timers3(Config) when is_list(Config) ->
1267    ?ACQUIRE_NODES(1, Config),
1268    M = build_dm_timers_message("1", "02", "31"),
1269    B = list_to_binary(M),
1270    Conf = flex_scanner_conf(Config),
1271    case decode_message(megaco_compact_text_encoder, false, [Conf], B) of
1272	{ok, M1} when is_record(M1,'MegacoMessage') ->
1273	    t("flex_compact_dm_timers3 -> "
1274	      "~n   M:  ~s"
1275	      "~n   M1: ~p", [M, M1]),
1276	    verify_dm_timers({1,2,31}, M1);
1277	Else ->
1278	    exit({decode_failed, M, Else})
1279    end.
1280
1281
1282flex_compact_dm_timers4(suite) ->
1283    [];
1284flex_compact_dm_timers4(Config) when is_list(Config) ->
1285    ?ACQUIRE_NODES(1, Config),
1286    M = build_dm_timers_message("10", "21", "99"),
1287    B = list_to_binary(M),
1288    Conf = flex_scanner_conf(Config),
1289    case decode_message(megaco_compact_text_encoder, false, [Conf], B) of
1290	{ok, M1} when is_record(M1,'MegacoMessage') ->
1291	    t("flex_compact_dm_timers4 -> "
1292	      "~n   M:  ~s"
1293	      "~n   M1: ~p", [M, M1]),
1294	    verify_dm_timers({10,21,99}, M1);
1295	Else ->
1296	    exit({decode_failed, M, Else})
1297    end.
1298
1299
1300flex_compact_dm_timers5(suite) ->
1301    [];
1302flex_compact_dm_timers5(Config) when is_list(Config) ->
1303    ?ACQUIRE_NODES(1, Config),
1304    M = build_dm_timers_message("99", "23", "11"),
1305    B = list_to_binary(M),
1306    Conf = flex_scanner_conf(Config),
1307    case decode_message(megaco_compact_text_encoder, false, [Conf], B) of
1308	{ok, M1} when is_record(M1,'MegacoMessage') ->
1309	    t("flex_compact_dm_timers5 -> "
1310	      "~n   M:  ~s"
1311	      "~n   M1: ~p", [M, M1]),
1312	    verify_dm_timers({99,23,11}, M1);
1313	Else ->
1314	    exit({decode_failed, M, Else})
1315    end.
1316
1317
1318flex_compact_dm_timers6(suite) ->
1319    [];
1320flex_compact_dm_timers6(Config) when is_list(Config) ->
1321    ?ACQUIRE_NODES(1, Config),
1322    M = build_dm_timers_message("77", "09", "1"),
1323    B = list_to_binary(M),
1324    Conf = flex_scanner_conf(Config),
1325    case decode_message(megaco_compact_text_encoder, false, [Conf], B) of
1326	{ok, M1} when is_record(M1,'MegacoMessage') ->
1327	    t("flex_compact_dm_timers6 -> "
1328	      "~n   M:  ~s"
1329	      "~n   M1: ~p", [M, M1]),
1330	    verify_dm_timers({77,9,1}, M1);
1331	Else ->
1332	    exit({decode_failed, M, Else})
1333    end.
1334
1335
1336flex_compact_dm_timers7(suite) ->
1337    [];
1338flex_compact_dm_timers7(Config) when is_list(Config) ->
1339    ?ACQUIRE_NODES(1, Config),
1340    M = build_dm_timers_message("77", "09", "1", "99"),
1341    B = list_to_binary(M),
1342    Conf = flex_scanner_conf(Config),
1343    case decode_message(megaco_compact_text_encoder, false, [Conf], B) of
1344	{ok, M1} when is_record(M1,'MegacoMessage') ->
1345	    t("flex_compact_dm_timers7 -> "
1346	      "~n   M:  ~s"
1347	      "~n   M1: ~p", [M, M1]),
1348	    verify_dm_timers({77,9,1,99}, M1);
1349	Else ->
1350	    exit({decode_failed, M, Else})
1351    end.
1352
1353
1354flex_compact_dm_timers8(suite) ->
1355    [];
1356flex_compact_dm_timers8(Config) when is_list(Config) ->
1357    ?ACQUIRE_NODES(1, Config),
1358    M = build_dm_timers_message("01", "09", "01", "02"),
1359    B = list_to_binary(M),
1360    Conf = flex_scanner_conf(Config),
1361    case decode_message(megaco_compact_text_encoder, false, [Conf], B) of
1362	{ok, M1} when is_record(M1,'MegacoMessage') ->
1363	    t("flex_compact_dm_timers8 -> "
1364	      "~n   M:  ~s"
1365	      "~n   M1: ~p", [M, M1]),
1366	    verify_dm_timers({1,9,1,2}, M1);
1367	Else ->
1368	    exit({decode_failed, M, Else})
1369    end.
1370
1371
1372build_dm_timers_message(T, S, L) ->
1373    TMRs = lists:flatten(io_lib:format("T:~s,S:~s,L:~s", [T, S, L])),
1374    build_dm_timers_message(TMRs).
1375
1376build_dm_timers_message(T, S, L, Z) ->
1377    TMRs = lists:flatten(io_lib:format("T:~s,S:~s,L:~s,Z:~s", [T, S, L,Z])),
1378    build_dm_timers_message(TMRs).
1379
1380build_dm_timers_message(TMRs) ->
1381    M = io_lib:format("!/" ?VERSION_STR " [123.123.123.4]:55555\nT=10001{C=-{MF=11111111/00000000/00000000{E=2223{al/on,dd/ce{DM=dialplan00}},SG{cg/rt},DM=dialplan00{~s,(0s| 00s|[1-7]xlxx|8lxxxxxxx|#xxxxxxx|*xx|9l1xxxxxxxxxx|9l011x.s)}}}}", [TMRs]),
1382    lists:flatten(M).
1383
1384
1385verify_dm_timers(TMRs, #'MegacoMessage'{mess = Mess}) ->
1386    #'Message'{messageBody = Body} = Mess,
1387    case get_dm_timers(Body) of
1388	{error, Reason} ->
1389	    exit({invalid_timer, {TMRs, Reason}});
1390	TMRs ->
1391	    ok;
1392	TMRs1 ->
1393	    exit({invalid_timer_values, {TMRs, TMRs1}})
1394    end.
1395
1396get_dm_timers({transactions, T}) when is_list(T) ->
1397    get_dm_timers1(T);
1398get_dm_timers(Other) ->
1399    {error, {invalid_transactions, Other}}.
1400
1401get_dm_timers1([{transactionRequest,T}|Ts])
1402  when is_record(T,'TransactionRequest') ->
1403    case get_dm_timers2(T) of
1404	{ok, Timers} ->
1405	    Timers;
1406	_ ->
1407	    get_dm_timers1(Ts)
1408    end;
1409get_dm_timers1([_|Ts]) ->
1410    get_dm_timers1(Ts);
1411get_dm_timers1([]) ->
1412    {error, {no_timers, 'TransactionRequest'}}.
1413
1414
1415get_dm_timers2(#'TransactionRequest'{actions = Actions}) when is_list(Actions) ->
1416    get_dm_timers3(Actions).
1417
1418
1419get_dm_timers3([#'ActionRequest'{commandRequests = Cmds}|Ars]) when is_list(Cmds) ->
1420    case get_dm_timers4(Cmds) of
1421	{ok, Timers} ->
1422	    {ok, Timers};
1423	_ ->
1424	    get_dm_timers3(Ars)
1425    end;
1426get_dm_timers3([_|Ars]) ->
1427    get_dm_timers3(Ars);
1428get_dm_timers3([]) ->
1429    {error, {no_timers, 'ActionRequest'}}.
1430
1431get_dm_timers4([#'CommandRequest'{command = Cmd}|Cmds]) ->
1432    case get_dm_timers5(Cmd) of
1433	{ok, Timers} ->
1434	    {ok, Timers};
1435	_ ->
1436	    get_dm_timers4(Cmds)
1437    end;
1438get_dm_timers4([_|Cmds]) ->
1439    get_dm_timers4(Cmds);
1440get_dm_timers4([]) ->
1441    {error, {no_timers, 'CommandRequest'}}.
1442
1443
1444get_dm_timers5({modReq, #'AmmRequest'{descriptors = Descriptors}}) ->
1445    get_dm_timers6(Descriptors);
1446get_dm_timers5(R) ->
1447    {error, {no_modReq, R}}.
1448
1449
1450get_dm_timers6([{digitMapDescriptor, #'DigitMapDescriptor'{digitMapValue = Val}}|_]) ->
1451    case Val of
1452	#'DigitMapValue'{startTimer    = T,
1453			 shortTimer    = S,
1454			 longTimer     = L,
1455			 durationTimer = asn1_NOVALUE} ->
1456	    {ok, {T, S, L}};
1457	#'DigitMapValue'{startTimer    = T,
1458			 shortTimer    = S,
1459			 longTimer     = L,
1460			 durationTimer = Z} ->
1461	    {ok, {T, S, L, Z}};
1462	_ ->
1463	    {error, no_value_in_dm}
1464    end;
1465get_dm_timers6([_|Descs]) ->
1466    get_dm_timers6(Descs);
1467get_dm_timers6([]) ->
1468    {error, {no_timers, descriptors}}.
1469
1470
1471%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1472
1473bin_test_msgs(suite) ->
1474    [];
1475bin_test_msgs(Config) when is_list(Config) ->
1476    ?ACQUIRE_NODES(1, Config),
1477    Msgs = msgs1() ++ msgs4(),
1478    DynamicDecode = false,
1479    test_msgs(megaco_binary_encoder, DynamicDecode, [], Msgs).
1480
1481
1482%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1483
1484ber_test_msgs(suite) ->
1485    [];
1486ber_test_msgs(Config) when is_list(Config) ->
1487    ?ACQUIRE_NODES(1, Config),
1488    Msgs = msgs1() ++ msgs4(),
1489    DynamicDecode = false,
1490    test_msgs(megaco_ber_encoder, DynamicDecode, [], Msgs).
1491
1492
1493%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1494
1495per_test_msgs(suite) ->
1496    [];
1497per_test_msgs(Config) when is_list(Config) ->
1498    ?ACQUIRE_NODES(1, Config),
1499    Msgs = msgs1() ++ msgs4(),
1500    DynamicDecode = false,
1501    test_msgs(megaco_per_encoder, DynamicDecode, [], Msgs).
1502
1503
1504%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1505
1506erl_dist_m_test_msgs(suite) ->
1507    [];
1508erl_dist_m_test_msgs(Config) when is_list(Config) ->
1509    ?ACQUIRE_NODES(1, Config),
1510    Msgs = msgs1() ++ msgs2() ++ msgs3() ++ msgs4(),
1511    DynamicDecode = false,
1512    Conf = [megaco_compressed],
1513    test_msgs(megaco_erl_dist_encoder, DynamicDecode, Conf, Msgs).
1514
1515
1516%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1517
1518%% # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # #
1519%% Ticket test cases:
1520
1521
1522%% --------------------------------------------------------------
1523%% Observe that this decode SHALL fail
1524compact_otp4011_msg1(suite) ->
1525    [];
1526compact_otp4011_msg1(Config) when is_list(Config) ->
1527%     put(severity,trc),
1528%     put(dbg,true),
1529    d("compact_otp4011_msg1 -> entry", []),
1530    ?ACQUIRE_NODES(1, Config),
1531    M = "!/" ?VERSION_STR " ML T=233350{C=${A=stedevice/01{M{O{MO=SR,RV=OFF,RG=OFF,tdmc/ec=OFF,MO=SR}}}}}",
1532    ok = compact_otp4011(M),
1533%     erase(severity),
1534%     erase(dbg),
1535    ok.
1536
1537
1538%% --------------------------------------------------------------
1539%% Observe that this decode SHALL fail
1540compact_otp4011_msg2(suite) ->
1541    [];
1542compact_otp4011_msg2(Config) when is_list(Config) ->
1543    d("compact_otp4011_msg2 -> entry", []),
1544    ?ACQUIRE_NODES(1, Config),
1545    M = "!/" ?VERSION_STR " ML T=233350{C=${A=stedevice/01{M{O{MO=SO,RV=OFF,RG=OFF,tdmc/ec=OFF,MO=SR}}}}}",
1546%     put(severity,trc),
1547%     put(dbg,true),
1548    ok = compact_otp4011(M).
1549
1550
1551%% --------------------------------------------------------------
1552%% Observe that this decode SHALL fail
1553compact_otp4011_msg3(suite) ->
1554    [];
1555compact_otp4011_msg3(Config) when is_list(Config) ->
1556    d("compact_otp4011_msg3 -> entry", []),
1557    ?ACQUIRE_NODES(1, Config),
1558    M = "!/" ?VERSION_STR " ML T=233350{C=${A=stedevice/01{M{O{MO=SR,RV=OFF,RG=OFF,tdmc/ec=OFF,MO=SO}}}}}",
1559%     put(severity,trc),
1560%     put(dbg,true),
1561    ok = compact_otp4011(M).
1562
1563
1564compact_otp4011(M) ->
1565    d("compact_otp4011 -> entry with"
1566      "~n   M: '~s'", [M]),
1567    Bin = list_to_binary(M),
1568    case decode_message(megaco_compact_text_encoder, false, [], Bin) of
1569	{ok, _} ->
1570	    exit({decoded_erroneous_message,M});
1571	{error, Error} when is_list(Error) -> % Expected result
1572	    d("compact_otp4011 -> expected error result (so far)", []),
1573	    case lists:keysearch(reason,1,Error) of
1574		{value, {reason,Reason}} ->
1575		    d("compact_otp4011 -> expected error: "
1576		      "~n   Reason: ~p", [Reason]),
1577		    case Reason of
1578			{0, megaco_text_parser_v2,
1579			 {do_merge_control_streamParms, [A,B]}}
1580			when is_list(A) andalso is_record(B, 'LocalControlDescriptor') ->
1581			    case lists:keysearch(mode,1,A) of
1582				{value, {mode, Mode}}
1583				when B#'LocalControlDescriptor'.streamMode /= asn1_NOVALUE ->
1584				    d("compact_otp4011 -> "
1585				      "expected error [~w]",[Mode]),
1586				    ok;
1587				Other ->
1588				    exit({unexpected_mode_reason, {A,B,Other}})
1589			    end;
1590			Other ->
1591			    exit({unexpected_reason, Other})
1592		    end;
1593
1594		false ->
1595		    d("compact_otp4011 -> OUPS, wrong kind of error", []),
1596		    exit({unexpected_result, Error})
1597	    end;
1598	Else ->
1599	    d("compact_otp4011 -> unexpected decode result: ~p", [Else]),
1600	    exit({unexpected_decode_result, Else})
1601    end.
1602
1603
1604%% --------------------------------------------------------------
1605%% Note that this decode SHALL fail, because of the misspelled
1606%% MEGCAO instead of the correct MEGACO.
1607compact_otp4013_msg1(suite) ->
1608    [];
1609compact_otp4013_msg1(Config) when is_list(Config) ->
1610    d("compact_otp4013_msg1 -> entry", []),
1611    ?ACQUIRE_NODES(1, Config),
1612    M = "MEGCAO/2 MG1 T=12345678{C=-{SC=root{SV{MT=RS,RE=901}}}}",
1613    Bin = list_to_binary(M),
1614    case decode_message(megaco_compact_text_encoder, false, [], Bin) of
1615	{ok, _} ->
1616	    exit({decoded_erroneous_message,M});
1617	{error, Reason} when is_list(Reason) ->
1618	    {value, {reason, no_version_found, _}} =
1619		lists:keysearch(reason, 1, Reason),
1620	    {value, {token, [{'SafeChars',_,"megcao/2"}|_]}} =
1621		lists:keysearch(token, 1, Reason),
1622	    ok;
1623	Else ->
1624	    exit({unexpected_decode_result,Else})
1625    end.
1626
1627
1628
1629%% --------------------------------------------------------------
1630%%
1631%%
1632compact_otp4085_msg1(suite) ->
1633    [];
1634compact_otp4085_msg1(Config) when is_list(Config) ->
1635    d("compact_otp4085_msg1 -> entry", []),
1636    ?ACQUIRE_NODES(1, Config),
1637    M = compact_otp4085_erroneous_msg(),
1638    Bin = list_to_binary(M),
1639    case decode_message(megaco_compact_text_encoder, false, [], Bin) of
1640	{ok, M} ->
1641	    exit({decoded_erroneous_message,M});
1642	{error, Error} when is_list(Error) -> % Expected result
1643	    t("compact_otp4085_msg1 -> decode failed", []),
1644	    case lists:keysearch(reason, 1, Error) of
1645		{value, {reason,{999999, Module, Crap}}} ->
1646		    t("compact_otp4085_msg1 -> THE ACTUAL ERROR: "
1647		      "~n   LINE NUMBER: 999999"
1648		      "~n   Module: ~p"
1649		      "~n   Crap:   ~p", [Module, Crap]),
1650		    %% ok;
1651		    exit({decode_failed_999999, Module, Crap});
1652		{value, {reason,{Line, Module, Crap}}} ->
1653		    t("compact_otp4085_msg1 -> Expected: "
1654		      "~n   Line:   ~p"
1655		      "~n   Module: ~p"
1656		      "~n   Crap:   ~p", [Line, Module, Crap]),
1657		    ok;
1658		false ->
1659		    exit({unexpected_result, Error})
1660	    end;
1661	Else ->
1662	    exit({unexpected_decode_result, Else})
1663    end.
1664
1665
1666%% --------------------------------------------------------------
1667%% This test case is just to show that the message used in
1668%% compact_otp4085_msg1 is actually ok when you add '}' at the end.
1669compact_otp4085_msg2(suite) ->
1670    [];
1671compact_otp4085_msg2(Config) when is_list(Config) ->
1672    d("compact_otp4085_msg1 -> entry", []),
1673    ?ACQUIRE_NODES(1, Config),
1674    M1 = compact_otp4085_erroneous_msg() ++ "}",
1675    Bin = list_to_binary(M1),
1676    case decode_message(megaco_compact_text_encoder, false, [], Bin) of
1677	{ok, M2} ->
1678	    l("compact_otp4085_msg1 -> successfull decode"
1679	      "~n   M2: ~p", [M2]),
1680	    ok;
1681	Else ->
1682	    e("compact_otp4085_msg1 -> decode error"
1683	      "~n   Else: ~p", [Else]),
1684	    exit({unexpected_decode_result,Else})
1685    end.
1686
1687
1688%% This message lack the ending parentesis (}).
1689compact_otp4085_erroneous_msg() ->
1690    M = "!/"
1691	?VERSION_STR
1692	" ML T=11223342{C=${A=${M{O{MO=SR,RV=OFF,RG=OFF},L{v=0,"
1693	"c=ATM NSAP $ ,"
1694	"a=eecid:$ ,"
1695	"m=audio - AAL1/ATMF -,"
1696	"}}},A=stee1181/01{M{O{MO=SR,RV=OFF,RG=OFF,tdmc/ec=off}}}}",
1697    M.
1698
1699%% --------------------------------------------------------------
1700%%
1701%%
1702compact_otp4280_msg1(suite) ->
1703    [];
1704compact_otp4280_msg1(Config) when is_list(Config) ->
1705    d("compact_otp4280_msg1 -> entry", []),
1706    ?ACQUIRE_NODES(1, Config),
1707    Bin = list_to_binary(compact_otp4280_msg()),
1708    case decode_message(megaco_compact_text_encoder, false, [], Bin) of
1709	{ok, _Msg} ->
1710	    ok;
1711	{error, Error} when is_list(Error) ->
1712	    t("compact_otp4280_msg1 -> decode failed", []),
1713	    case lists:keysearch(reason, 1, Error) of
1714		{value, {reason,{Line, Module, Reason} = R}} ->
1715		    t("compact_otp4280_msg1 -> "
1716		      "~n   Line:   ~w"
1717		      "~n   Module: ~w"
1718		      "~n   Reason: ~w", [Line, Module, Reason]),
1719		    exit({decode_failed, R});
1720		false ->
1721		    exit({unexpected_result, Error})
1722	    end;
1723	Else ->
1724	    exit({unexpected_decode_result, Else})
1725    end.
1726
1727compact_otp4280_msg() ->
1728    M = "!/"
1729	?VERSION_STR
1730	" mgw1 P=71853646{C=-{AV=root{M{TS{root/maxnumberofcontexts=49500,"
1731	"root/maxterminationspercontext=2,root/normalmgexecutiontime=200,"
1732	"root/normalmgcexecutiontime=150,"
1733	"root/provisionalresponsetimervalue=2000,BF=OFF,SI=IV}}}}}",
1734    M.
1735
1736
1737%% --------------------------------------------------------------
1738%% This ticket is about comments in a message
1739compact_otp4299_msg1(suite) ->
1740    [];
1741compact_otp4299_msg1(Config) when is_list(Config) ->
1742    d("compact_otp4299_msg1 -> entry", []),
1743    ?ACQUIRE_NODES(1, Config),
1744    Bin = list_to_binary(compact_otp4299_msg()),
1745    case decode_message(megaco_compact_text_encoder, false, [], Bin) of
1746	{ok, _Msg} ->
1747	    ok;
1748
1749	{error, Reason} ->
1750	    exit({decode_error, Reason});
1751
1752	Else ->
1753	    exit({unexpected_decode_result, Else})
1754    end.
1755
1756
1757%% Same message, but this time decoded using the flex scanner
1758compact_otp4299_msg2(suite) ->
1759    [];
1760compact_otp4299_msg2(Config) when is_list(Config) ->
1761    d("compact_otp4299_msg2 -> entry", []),
1762    ?ACQUIRE_NODES(1, Config),
1763
1764    {Pid, Conf} = compact_otp4299_msg2_init(),
1765
1766    Bin = list_to_binary(compact_otp4299_msg()),
1767    Res = decode_message(megaco_compact_text_encoder, false, [Conf], Bin),
1768    compact_otp4299_msg2_finish(Pid),
1769
1770    case Res of
1771	{ok, _Msg} ->
1772	    ok;
1773
1774	{error, Reason} ->
1775	    exit({decode_error, Reason});
1776
1777	Else ->
1778	    exit({unexpected_decode_result, Else})
1779    end.
1780
1781
1782compact_otp4299_msg2_init() ->
1783    Flag = process_flag(trap_exit, true),
1784    Res = (catch start_flex_scanner()),
1785    process_flag(trap_exit, Flag),
1786    case Res of
1787	{error, Reason} ->
1788	    skip(Reason);
1789	{ok, FlexConfig} ->
1790	    FlexConfig
1791    end.
1792
1793compact_otp4299_msg2_finish(Pid) ->
1794    stop_flex_scanner(Pid).
1795
1796
1797compact_otp4299_msg() ->
1798    M = ";KALLE\n"
1799	"!/"
1800	?VERSION_STR
1801	" mg58_1 P=005197711{; YET ANOTHER COMMENT\n"
1802	"C=035146207{A=mg58_1_1_4_1_23/19; BEFORE COMMA\n"
1803	",; AFTER COMMA\n"
1804	"A=eph58_1/0xA4023371{M{L{\n"
1805	"v=0\n"
1806	"c=ATM NSAP 39.0102.0304.0506.0708.090a.0b58.0100.0000.0000.00\n"
1807	"m=audio - AAL1/ATMF -\n"
1808	"a=eecid:A4023371\n"
1809	"}}; HOBBE\n}; KALLE \"HOBBE \n}}"
1810	";KALLE\n\n",
1811    M.
1812
1813
1814%% --------------------------------------------------------------
1815%%
1816%%
1817compact_otp4359_msg1(suite) ->
1818    [];
1819compact_otp4359_msg1(Config) when is_list(Config) ->
1820    d("compact_otp4359_msg1 -> entry", []),
1821    ?ACQUIRE_NODES(1, Config),
1822    Bin = list_to_binary(compact_otp4359_msg()),
1823    case decode_message(megaco_compact_text_encoder, false, [], Bin) of
1824	{ok, #'MegacoMessage'{mess = Mess}} ->
1825	    {transactions, Trans} = Mess#'Message'.messageBody,
1826	    case Trans of
1827		[{transactionRequest,#'TransactionRequest'{transactionId = asn1_NOVALUE}}] ->
1828		    ok;
1829		_ ->
1830		    exit({unexpected_transactions, Trans})
1831	    end;
1832	Else ->
1833	    t("compact_otp4359_msg1 -> "
1834	      "~n   Else: ~w", [Else]),
1835	    exit({unexpected_decode_result, Else})
1836    end.
1837
1838compact_otp4359_msg() ->
1839    M = "!/" ?VERSION_STR " ml2 T={C=${A=${M{O {MO=SR,RG=OFF,RV=OFF}}}}}",
1840    M.
1841
1842
1843%% --------------------------------------------------------------
1844%%
1845%%
1846compact_otp4920_msg0(suite) ->
1847    [];
1848compact_otp4920_msg0(Config) when is_list(Config) ->
1849    d("compact_otp4920_msg0 -> entry", []),
1850    ?ACQUIRE_NODES(1, Config),
1851						%    put(dbg,true),
1852    compact_otp4920_msg_1(compact_otp4920_msg0(), true).
1853
1854compact_otp4920_msg1(suite) ->
1855    [];
1856compact_otp4920_msg1(Config) when is_list(Config) ->
1857    d("compact_otp4920_msg1 -> entry", []),
1858    ?ACQUIRE_NODES(1, Config),
1859						%    put(dbg,true),
1860    compact_otp4920_msg_1(compact_otp4920_msg1(), false).
1861
1862compact_otp4920_msg2(suite) ->
1863    [];
1864compact_otp4920_msg2(Config) when is_list(Config) ->
1865    d("compact_otp4920_msg2 -> entry", []),
1866    ?ACQUIRE_NODES(1, Config),
1867    compact_otp4920_msg_1(compact_otp4920_msg2(), false).
1868
1869compact_otp4920_msg3(suite) ->
1870    [];
1871compact_otp4920_msg3(Config) when is_list(Config) ->
1872    d("compact_otp4920_msg3 -> entry", []),
1873    ?ACQUIRE_NODES(1, Config),
1874    compact_otp4920_msg_1(compact_otp4920_msg3(), true).
1875
1876compact_otp4920_msg4(suite) ->
1877    [];
1878compact_otp4920_msg4(Config) when is_list(Config) ->
1879    d("compact_otp4920_msg4 -> entry", []),
1880    ?ACQUIRE_NODES(1, Config),
1881    compact_otp4920_msg_1(compact_otp4920_msg4(), true).
1882
1883compact_otp4920_msg5(suite) ->
1884    [];
1885compact_otp4920_msg5(Config) when is_list(Config) ->
1886    d("compact_otp4920_msg5 -> entry", []),
1887    ?ACQUIRE_NODES(1, Config),
1888    compact_otp4920_msg_1(compact_otp4920_msg5(), true).
1889
1890compact_otp4920_msg6(suite) ->
1891    [];
1892compact_otp4920_msg6(Config) when is_list(Config) ->
1893    d("compact_otp4920_msg6 -> entry", []),
1894    ?ACQUIRE_NODES(1, Config),
1895    compact_otp4920_msg_1(compact_otp4920_msg6(), true).
1896
1897compact_otp4920_msg7(suite) ->
1898    [];
1899compact_otp4920_msg7(Config) when is_list(Config) ->
1900    d("compact_otp4920_msg7 -> entry", []),
1901    ?ACQUIRE_NODES(1, Config),
1902						%    put(dbg,true),
1903    compact_otp4920_msg_1(compact_otp4920_msg7(), true).
1904
1905compact_otp4920_msg8(suite) ->
1906    [];
1907compact_otp4920_msg8(Config) when is_list(Config) ->
1908    d("compact_otp4920_msg8 -> entry", []),
1909    ?ACQUIRE_NODES(1, Config),
1910						%    put(dbg,true),
1911    compact_otp4920_msg_1(compact_otp4920_msg8(), false).
1912
1913compact_otp4920_msg9(suite) ->
1914    [];
1915compact_otp4920_msg9(Config) when is_list(Config) ->
1916    d("compact_otp4920_msg9 -> entry", []),
1917    ?ACQUIRE_NODES(1, Config),
1918    compact_otp4920_msg_1(compact_otp4920_msg9(), false).
1919
1920compact_otp4920_msg10(suite) ->
1921    [];
1922compact_otp4920_msg10(Config) when is_list(Config) ->
1923    d("compact_otp4920_msg10 -> entry", []),
1924    ?ACQUIRE_NODES(1, Config),
1925    compact_otp4920_msg_1(compact_otp4920_msg10(), false).
1926
1927compact_otp4920_msg11(suite) ->
1928    [];
1929compact_otp4920_msg11(Config) when is_list(Config) ->
1930    d("compact_otp4920_msg11 -> entry", []),
1931    ?ACQUIRE_NODES(1, Config),
1932    compact_otp4920_msg_1(compact_otp4920_msg11(), false).
1933
1934compact_otp4920_msg12(suite) ->
1935    [];
1936compact_otp4920_msg12(Config) when is_list(Config) ->
1937    d("compact_otp4920_msg12 -> entry", []),
1938    ?ACQUIRE_NODES(1, Config),
1939    compact_otp4920_msg_1(compact_otp4920_msg12(), true).
1940
1941%% Duplicate padding
1942compact_otp4920_msg20(suite) ->
1943    [];
1944compact_otp4920_msg20(Config) when is_list(Config) ->
1945    d("compact_otp4920_msg20 -> entry", []),
1946    ?ACQUIRE_NODES(1, Config),
1947    compact_otp4920_msg_2(compact_otp4920_msg20(), bad_mid_duplicate_padding).
1948
1949%% Length
1950compact_otp4920_msg21(suite) ->
1951    [];
1952compact_otp4920_msg21(Config) when is_list(Config) ->
1953    d("compact_otp4920_msg21 -> entry", []),
1954    ?ACQUIRE_NODES(1, Config),
1955    compact_otp4920_msg_2(compact_otp4920_msg21(), bad_mid_ip6addr_length).
1956
1957%% Length
1958compact_otp4920_msg22(suite) ->
1959    [];
1960compact_otp4920_msg22(Config) when is_list(Config) ->
1961    d("compact_otp4920_msg22 -> entry", []),
1962    ?ACQUIRE_NODES(1, Config),
1963    compact_otp4920_msg_2(compact_otp4920_msg22(), bad_mid_ip6addr_length).
1964
1965%% Length
1966compact_otp4920_msg23(suite) ->
1967    [];
1968compact_otp4920_msg23(Config) when is_list(Config) ->
1969    d("compact_otp4920_msg23 -> entry", []),
1970    ?ACQUIRE_NODES(1, Config),
1971    compact_otp4920_msg_2(compact_otp4920_msg23(), bad_mid_ip6addr_length).
1972
1973%% Length
1974compact_otp4920_msg24(suite) ->
1975    [];
1976compact_otp4920_msg24(Config) when is_list(Config) ->
1977    d("compact_otp4920_msg24 -> entry", []),
1978    ?ACQUIRE_NODES(1, Config),
1979    compact_otp4920_msg_2(compact_otp4920_msg24(), bad_mid_ip6addr_length).
1980
1981%% Length
1982compact_otp4920_msg25(suite) ->
1983    [];
1984compact_otp4920_msg25(Config) when is_list(Config) ->
1985    d("compact_otp4920_msg25 -> entry", []),
1986    ?ACQUIRE_NODES(1, Config),
1987    compact_otp4920_msg_2(compact_otp4920_msg25(), bad_mid_ip6addr_length).
1988
1989compact_otp4920_msg_1(M1, CheckEqual) ->
1990    Bin1 = list_to_binary(M1),
1991    case decode_message(megaco_compact_text_encoder, false, [], Bin1) of
1992	{ok, Msg} ->
1993 	    io:format(" decoded", []),
1994	    case encode_message(megaco_compact_text_encoder, [], Msg) of
1995		{ok, Bin1} ->
1996		    io:format(", encoded - equal:", []),
1997		    ok;
1998		{ok, Bin2} when is_binary(Bin2) andalso (CheckEqual =:= true) ->
1999		    M2 = binary_to_list(Bin2),
2000		    io:format(", encoded - not equal:", []),
2001		    exit({messages_not_equal, M1, M2});
2002		{ok, _} ->
2003		    io:format(", encoded:", []),
2004		    ok;
2005		Else ->
2006		    io:format(", encode failed:", []),
2007		    exit({unexpected_encode_result, Else})
2008	    end;
2009	Else ->
2010	    io:format("decode failed:", []),
2011	    exit({unexpected_decode_result, Else})
2012    end.
2013
2014compact_otp4920_msg_2(M1, ExpectedReason) ->
2015    Bin = list_to_binary(M1),
2016    case decode_message(megaco_compact_text_encoder, false, [], Bin) of
2017	{ok, Msg} ->
2018	    io:format("unexpected successfull decode", []),
2019	    exit({unexpected_encode_ok, Msg});
2020	{error, [{reason, {__Line, _Mod, Reason}}|_]} ->
2021	    case element(1, Reason) of
2022		ExpectedReason ->
2023		    ok;
2024		_ ->
2025		    exit({unexpected_decode_error_reason,
2026			  ExpectedReason, Reason})
2027	    end;
2028	{error, [{reason, {_Mod, Reason}}|_]} ->
2029	    case element(1, Reason) of
2030		ExpectedReason ->
2031		    ok;
2032		_ ->
2033		    exit({unexpected_decode_error_reason,
2034			  ExpectedReason, Reason})
2035	    end;
2036	Else ->
2037	    io:format("unexpected decode result", []),
2038	    exit({unexpected_decode_result, Else})
2039
2040    end.
2041
2042compact_otp4920_msg0() ->
2043    M = "!/" ?VERSION_STR " [192.168.30.1]\nT=100{C=${A=${M{O{MO=SR,RG=OFF,RV=OFF}}}}}",
2044    M.
2045
2046compact_otp4920_msg1() ->
2047    M = "!/" ?VERSION_STR " [2031:0000:130F:0000:0000:09C0:876A:130B]\nT=101{C=${A=${M{O{MO=SR,RG=OFF,RV=OFF}}}}}",
2048    M.
2049
2050compact_otp4920_msg2() ->
2051    M = "!/" ?VERSION_STR " [2031:0:130F:0:0:9C0:876A:130B]\nT=102{C=${A=${M{O{MO=SR,RG=OFF,RV=OFF}}}}}",
2052    M.
2053
2054compact_otp4920_msg3() ->
2055    M = "!/" ?VERSION_STR " [2031:0:130F::9C0:876A:130B]\nT=103{C=${A=${M{O{MO=SR,RG=OFF,RV=OFF}}}}}",
2056    M.
2057
2058compact_otp4920_msg4() ->
2059    M = "!/" ?VERSION_STR " [::1]\nT=104{C=${A=${M{O{MO=SR,RG=OFF,RV=OFF}}}}}",
2060    M.
2061
2062compact_otp4920_msg5() ->
2063    M = "!/" ?VERSION_STR " [::]\nT=105{C=${A=${M{O{MO=SR,RG=OFF,RV=OFF}}}}}",
2064    M.
2065
2066compact_otp4920_msg6() ->
2067    M = "!/" ?VERSION_STR " [1::]\nT=106{C=${A=${M{O{MO=SR,RG=OFF,RV=OFF}}}}}",
2068    M.
2069
2070compact_otp4920_msg7() ->
2071    M = "!/" ?VERSION_STR " [FEDC:1::]\nT=107{C=${A=${M{O{MO=SR,RG=OFF,RV=OFF}}}}}",
2072    M.
2073
2074compact_otp4920_msg8() ->
2075    M = "!/" ?VERSION_STR " [2031:0:130F:0:0:9C0:135.106.19.11]\nT=108{C=${A=${M{O{MO=SR,RG=OFF,RV=OFF}}}}}",
2076    M.
2077
2078compact_otp4920_msg9() ->
2079    M = "!/" ?VERSION_STR " [2031:0:130F::9C0:135.106.19.11]\nT=109{C=${A=${M{O{MO=SR,RG=OFF,RV=OFF}}}}}",
2080    M.
2081
2082compact_otp4920_msg10() ->
2083    M = "!/" ?VERSION_STR " [::FFFF:192.168.30.1]\nT=110{C=${A=${M{O{MO=SR,RG=OFF,RV=OFF}}}}}",
2084    M.
2085
2086compact_otp4920_msg11() ->
2087    M = "!/" ?VERSION_STR " [::192.168.30.1]\nT=111{C=${A=${M{O{MO=SR,RG=OFF,RV=OFF}}}}}",
2088    M.
2089
2090compact_otp4920_msg12() ->
2091    M = "!/" ?VERSION_STR " [::C0A8:1E01]\nT=112{C=${A=${M{O{MO=SR,RG=OFF,RV=OFF}}}}}",
2092    M.
2093
2094%% Illegal: only one :: allowed
2095compact_otp4920_msg20() ->
2096    M = "!/" ?VERSION_STR " [2031::130F::9C0]\nT=120{C=${A=${M{O{MO=SR,RG=OFF,RV=OFF}}}}}",
2097    M.
2098
2099%% Illegal: length
2100compact_otp4920_msg21() ->
2101    M = "!/" ?VERSION_STR " [2031:FFEE:0000:130F:0000:0000:09C0:876A:130B]\nT=121{C=${A=${M{O{MO=SR,RG=OFF,RV=OFF}}}}}",
2102    M.
2103
2104%% Illegal: length
2105compact_otp4920_msg22() ->
2106    M = "!/" ?VERSION_STR " [2031:FFEE:0:130F:0:0:9C0:135.106.19.11]\nT=122{C=${A=${M{O{MO=SR,RG=OFF,RV=OFF}}}}}",
2107    M.
2108
2109%% Illegal: length
2110compact_otp4920_msg23() ->
2111    M = "!/" ?VERSION_STR " [2031:FFEE:0000:130F:2132:4354::09C0:876A:130B]\nT=123{C=${A=${M{O{MO=SR,RG=OFF,RV=OFF}}}}}",
2112    M.
2113
2114%% Illegal: length
2115compact_otp4920_msg24() ->
2116    M = "!/" ?VERSION_STR " [::2031:FFEE:0000:130F:2132:4354:09C0:876A:130B]\nT=124{C=${A=${M{O{MO=SR,RG=OFF,RV=OFF}}}}}",
2117    M.
2118
2119%% Illegal: length
2120compact_otp4920_msg25() ->
2121    M = "!/" ?VERSION_STR " [2031:FFEE:0000:130F:2132:4354:09C0:876A:130B::]\nT=125{C=${A=${M{O{MO=SR,RG=OFF,RV=OFF}}}}}",
2122    M.
2123
2124
2125compact_otp5186_msg01(suite) ->
2126    [];
2127compact_otp5186_msg01(Config) when is_list(Config) ->
2128    d("compact_otp5186_msg01 -> entry", []),
2129    ?ACQUIRE_NODES(1, Config),
2130    compact_otp5186_msg_1(compact_otp5186_msg01(), error, ignore).
2131
2132compact_otp5186_msg02(suite) ->
2133    [];
2134compact_otp5186_msg02(Config) when is_list(Config) ->
2135    d("compact_otp5186_msg02 -> entry", []),
2136    ?ACQUIRE_NODES(1, Config),
2137    compact_otp5186_msg_1(compact_otp5186_msg02(), ok, ok).
2138
2139compact_otp5186_msg03(suite) ->
2140    [];
2141compact_otp5186_msg03(Config) when is_list(Config) ->
2142    d("compact_otp5186_msg03 -> entry", []),
2143    ?ACQUIRE_NODES(1, Config),
2144    compact_otp5186_msg_2(compact_otp5186_msg03(), ok, ok).
2145
2146compact_otp5186_msg04(suite) ->
2147    [];
2148compact_otp5186_msg04(Config) when is_list(Config) ->
2149    d("compact_otp5186_msg04 -> entry", []),
2150    ?ACQUIRE_NODES(1, Config),
2151    compact_otp5186_msg_2(compact_otp5186_msg04(), ok, ok).
2152
2153compact_otp5186_msg05(suite) ->
2154    [];
2155compact_otp5186_msg05(Config) when is_list(Config) ->
2156    d("compact_otp5186_msg05 -> entry", []),
2157    ?ACQUIRE_NODES(1, Config),
2158    compact_otp5186_msg_2(compact_otp5186_msg05(), ok, ok).
2159
2160compact_otp5186_msg06(suite) ->
2161    [];
2162compact_otp5186_msg06(Config) when is_list(Config) ->
2163    d("compact_otp5186_msg06 -> entry", []),
2164    ?ACQUIRE_NODES(1, Config),
2165    compact_otp5186_msg_2(compact_otp5186_msg06(), ok, ok).
2166
2167compact_otp5186_msg_1(M1, DecodeExpect, EncodeExpect) ->
2168    Bin1 = list_to_binary(M1),
2169    case decode_message(megaco_compact_text_encoder, false, [], Bin1) of
2170	{ok, Msg} when DecodeExpect == ok ->
2171 	    io:format(" decoded", []),
2172	    case encode_message(megaco_compact_text_encoder, [], Msg) of
2173		{ok, Bin1} when EncodeExpect == ok ->
2174		    io:format(", encoded - equal:", []),
2175		    ok;
2176		{ok, Bin2} when EncodeExpect == ok ->
2177		    M2 = binary_to_list(Bin2),
2178		    io:format(", encoded - not equal:", []),
2179		    exit({messages_not_equal, Msg, M1, M2});
2180		{ok, Bin3} when EncodeExpect == error ->
2181		    M3 = binary_to_list(Bin3),
2182		    io:format(", unexpected encode:", []),
2183		    exit({unexpected_encode_success, Msg, M1, M3});
2184		_Else when EncodeExpect == error ->
2185		    io:format(", encode failed ", []),
2186		    ok
2187	    end;
2188	{ok, Msg} when DecodeExpect == error ->
2189 	    io:format(" decoded", []),
2190	    exit({unexpected_decode_success, Msg});
2191	_Else when DecodeExpect == error ->
2192	    io:format(" decode failed ", []),
2193	    ok;
2194	Else when DecodeExpect == ok ->
2195	    io:format(" decode failed ", []),
2196	    exit({unexpected_decode_result, Else})
2197    end.
2198
2199compact_otp5186_msg_2(Msg1, EncodeExpect, DecodeExpect) ->
2200    case encode_message(megaco_compact_text_encoder, [], Msg1) of
2201	{ok, Bin} when EncodeExpect == ok ->
2202 	    io:format(" encoded", []),
2203	    case decode_message(megaco_compact_text_encoder, false, [], Bin) of
2204		{ok, Msg1} when DecodeExpect == ok ->
2205		    io:format(", decoded - equal:", []),
2206		    ok;
2207		{ok, Msg2} when DecodeExpect == ok ->
2208		    M = binary_to_list(Bin),
2209		    case (catch compact_otp5186_check_megamsg(Msg1, Msg2)) of
2210			ok ->
2211			    io:format(", decoded - not equal - ok:", []),
2212			    ok;
2213			{'EXIT', Reason} ->
2214			    io:format(", decoded - not equal:", []),
2215			    exit({messages_not_equal, M, Reason, Msg1, Msg2})
2216		    end;
2217		{ok, Msg3} when DecodeExpect == error ->
2218		    M = binary_to_list(Bin),
2219		    io:format(", decoded:", []),
2220		    exit({unexpected_decode_success, M, Msg1, Msg3});
2221		Else when DecodeExpect == ok ->
2222		    M = binary_to_list(Bin),
2223		    io:format(", decode failed ", []),
2224		    exit({unexpected_decode_success, Msg1, M, Else});
2225		_Else when DecodeExpect == error ->
2226		    io:format(", decode failed ", []),
2227		    ok
2228	    end;
2229	{ok, Bin} when EncodeExpect == error ->
2230	    M = binary_to_list(Bin),
2231	    io:format(" encoded", []),
2232	    exit({unexpected_encode_success, Msg1, M});
2233	_Else when EncodeExpect == error ->
2234	    io:format(" encode failed ", []),
2235	    ok;
2236	Else when EncodeExpect == ok ->
2237	    io:format(" encode failed ", []),
2238	    exit({unexpected_encode_result, Else})
2239    end.
2240
2241
2242%% --
2243
2244compact_otp5186_msg01() ->
2245    "!/2 <mg5>\nP=67111298{C=2699{AV=mg5_ipeph/0x0f0001{}}}".
2246
2247compact_otp5186_msg02() ->
2248    "!/2 <mg5>\nP=67111298{C=2699{AV=mg5_ipeph/0x0f0001}}".
2249
2250compact_otp5186_msg03() ->
2251    {'MegacoMessage',
2252     asn1_NOVALUE,
2253     {'Message',
2254      2,
2255      {domainName,{'DomainName',"mg5",asn1_NOVALUE}},
2256      {transactions,
2257       [{transactionReply,
2258	 {'TransactionReply',67111298,asn1_NOVALUE,
2259	  {actionReplies,[
2260			  {'ActionReply',2699,asn1_NOVALUE,asn1_NOVALUE,
2261			   [
2262			    {auditValueReply,
2263			     {auditResult,
2264			      {'AuditResult',
2265			       {megaco_term_id,false,["mg5_ipeph","0x0f0001"]},
2266			       [
2267			       ]
2268			      }
2269			     }
2270			    }
2271			   ]
2272			  }
2273			 ]
2274	  }
2275	 }
2276	}
2277       ]
2278      }
2279     }
2280    }.
2281
2282compact_otp5186_msg04() ->
2283    {'MegacoMessage',asn1_NOVALUE,
2284     {'Message',2,{domainName,{'DomainName',"mg5",asn1_NOVALUE}},
2285      {transactions,
2286       [{transactionReply,
2287	 {'TransactionReply',67111298,asn1_NOVALUE,
2288	  {actionReplies,[
2289			  {'ActionReply',2699,asn1_NOVALUE,asn1_NOVALUE,
2290			   [
2291			    {auditValueReply,
2292			     {auditResult,
2293			      {'AuditResult',
2294			       {megaco_term_id,false,["mg5_ipeph","0x0f0001"]},
2295			       [
2296				{emptyDescriptors,
2297				 {'AuditDescriptor',asn1_NOVALUE,asn1_NOVALUE}
2298				}
2299			       ]
2300			      }
2301			     }
2302			    }
2303			   ]
2304			  }
2305			 ]
2306	  }
2307	 }
2308	}
2309       ]
2310      }
2311     }
2312    }.
2313
2314compact_otp5186_msg05() ->
2315    {'MegacoMessage',
2316     asn1_NOVALUE,
2317     {'Message',
2318      2,
2319      {domainName,{'DomainName',"mg5",asn1_NOVALUE}},
2320      {transactions,
2321       [{transactionReply,
2322	 {'TransactionReply',67111298,asn1_NOVALUE,
2323	  {actionReplies,[
2324			  {'ActionReply',2699,asn1_NOVALUE,asn1_NOVALUE,
2325			   [
2326			    {addReply,
2327			     {'AmmsReply',
2328			      [
2329			       {megaco_term_id,false,["mg5_ipeph","0x0f0001"]}
2330			      ],
2331			      [
2332			      ]
2333			     }
2334			    }
2335			   ]
2336			  }
2337			 ]
2338	  }
2339	 }
2340	}
2341       ]
2342      }
2343     }
2344    }.
2345
2346compact_otp5186_msg06() ->
2347    {'MegacoMessage',asn1_NOVALUE,
2348     {'Message',2,{domainName,{'DomainName',"mg5",asn1_NOVALUE}},
2349      {transactions,
2350       [{transactionReply,
2351	 {'TransactionReply',67111298,asn1_NOVALUE,
2352	  {actionReplies,[
2353			  {'ActionReply',2699,asn1_NOVALUE,asn1_NOVALUE,
2354			   [
2355			    {addReply,
2356			     {'AmmsReply',
2357			      [
2358			       {megaco_term_id,false,["mg5_ipeph","0x0f0001"]}
2359			      ],
2360			      [
2361			       {emptyDescriptors,
2362				{'AuditDescriptor',asn1_NOVALUE,asn1_NOVALUE}
2363			       }
2364			      ]
2365			     }
2366			    }
2367			   ]
2368			  }
2369			 ]
2370	  }
2371	 }
2372	}
2373       ]
2374      }
2375     }
2376    }.
2377
2378%% --
2379
2380compact_otp5186_check_megamsg(M1, M1) ->
2381    ok;
2382compact_otp5186_check_megamsg(#'MegacoMessage'{authHeader = AH,
2383					       mess = M1},
2384			      #'MegacoMessage'{authHeader = AH,
2385					       mess = M2}) ->
2386    compact_otp5186_check_mess(M1, M2);
2387compact_otp5186_check_megamsg(#'MegacoMessage'{authHeader = AH1},
2388			      #'MegacoMessage'{authHeader = AH2}) ->
2389    exit({not_equal, authHeader, AH1, AH2}).
2390
2391compact_otp5186_check_mess(M, M) ->
2392    ok;
2393compact_otp5186_check_mess(#'Message'{version     = V,
2394				      mId         = MId,
2395				      messageBody = B1},
2396			   #'Message'{version     = V,
2397				      mId         = MId,
2398				      messageBody = B2}) ->
2399    compact_otp5186_check_body(B1, B2);
2400compact_otp5186_check_mess(#'Message'{version     = V,
2401				      mId         = MId1},
2402			   #'Message'{version     = V,
2403				      mId         = MId2}) ->
2404    exit({not_equal, mId, MId1, MId2});
2405compact_otp5186_check_mess(#'Message'{version     = V1,
2406				      mId         = MId},
2407			   #'Message'{version     = V2,
2408				      mId         = MId}) ->
2409    exit({not_equal, version, V1, V2}).
2410
2411compact_otp5186_check_body(B, B) ->
2412    ok;
2413compact_otp5186_check_body({transactions, T1}, {transactions, T2}) ->
2414    compact_otp5186_check_trans(T1, T2);
2415compact_otp5186_check_body({messageError, E1}, {messageError, E2}) ->
2416    compact_otp5186_check_merr(E1, E2);
2417compact_otp5186_check_body(B1, B2) ->
2418    exit({not_equal, messageBody, B1, B2}).
2419
2420compact_otp5186_check_trans([], []) ->
2421    ok;
2422compact_otp5186_check_trans([], T2) ->
2423    exit({not_equal, transactions, [], T2});
2424compact_otp5186_check_trans(T1, []) ->
2425    exit({not_equal, transactions, T1, []});
2426compact_otp5186_check_trans([Tran1|Trans1], [Tran2|Trans2]) ->
2427    compact_otp5186_check_trans(Trans1, Trans2),
2428    compact_otp5186_check_transaction(Tran1, Tran2).
2429
2430compact_otp5186_check_merr(ME, ME) ->
2431    ok;
2432compact_otp5186_check_merr(#'ErrorDescriptor'{errorCode = EC,
2433					      errorText = ET1},
2434			   #'ErrorDescriptor'{errorCode = EC,
2435					      errorText = ET2}) ->
2436    exit({not_equal, errorText, ET1, ET2});
2437compact_otp5186_check_merr(#'ErrorDescriptor'{errorCode = EC1,
2438					      errorText = ET},
2439			   #'ErrorDescriptor'{errorCode = EC2,
2440					      errorText = ET}) ->
2441    exit({not_equal, errorCode, EC1, EC2}).
2442
2443compact_otp5186_check_transaction(T, T) ->
2444    ok;
2445compact_otp5186_check_transaction({transactionReply, TR1},
2446				  {transactionReply, TR2}) ->
2447    compact_otp5186_check_transRep(TR1, TR2);
2448compact_otp5186_check_transaction(T1, T2) ->
2449    exit({unexpected_transactions, T1, T2}).
2450
2451compact_otp5186_check_transRep(T, T) ->
2452    ok;
2453compact_otp5186_check_transRep(#'TransactionReply'{transactionId     = TId,
2454						   immAckRequired    = IAR,
2455						   transactionResult = TR1},
2456			       #'TransactionReply'{transactionId     = TId,
2457						   immAckRequired    = IAR,
2458						   transactionResult = TR2}) ->
2459    compact_otp5186_check_transRes(TR1, TR2);
2460compact_otp5186_check_transRep(T1, T2) ->
2461    exit({unexpected_transaction_reply, T1, T2}).
2462
2463compact_otp5186_check_transRes(TR, TR) ->
2464    ok;
2465compact_otp5186_check_transRes({actionReplies, AR1},
2466			       {actionReplies, AR2}) ->
2467    compact_otp5186_check_actReps(AR1, AR2);
2468compact_otp5186_check_transRes(TR1, TR2) ->
2469    exit({unexpected_transaction_result, TR1, TR2}).
2470
2471compact_otp5186_check_actReps([], []) ->
2472    ok;
2473compact_otp5186_check_actReps(AR1, []) ->
2474    exit({not_equal, actionReplies, AR1, []});
2475compact_otp5186_check_actReps([], AR2) ->
2476    exit({not_equal, actionReplies, [], AR2});
2477compact_otp5186_check_actReps([AR1|ARs1], [AR2|ARs2]) ->
2478    compact_otp5186_check_actRep(AR1, AR2),
2479    compact_otp5186_check_actReps(ARs1, ARs2).
2480
2481compact_otp5186_check_actRep(AR, AR) ->
2482    ok;
2483compact_otp5186_check_actRep(#'ActionReply'{contextId       = ID,
2484					    errorDescriptor = ED,
2485					    contextReply    = CtxRep,
2486					    commandReply    = CmdRep1},
2487			     #'ActionReply'{contextId       = ID,
2488					    errorDescriptor = ED,
2489					    contextReply    = CtxRep,
2490					    commandReply    = CmdRep2}) ->
2491    compact_otp5186_check_cmdReps(CmdRep1, CmdRep2);
2492compact_otp5186_check_actRep(AR1, AR2) ->
2493    exit({unexpected_actionReply, AR1, AR2}).
2494
2495compact_otp5186_check_cmdReps([], []) ->
2496    ok;
2497compact_otp5186_check_cmdReps(CR1, []) ->
2498    exit({not_equal, commandReplies, CR1, []});
2499compact_otp5186_check_cmdReps([], CR2) ->
2500    exit({not_equal, commandReplies, [], CR2});
2501compact_otp5186_check_cmdReps([CR1|CRs1], [CR2|CRs2]) ->
2502    compact_otp5186_check_cmdRep(CR1, CR2),
2503    compact_otp5186_check_cmdReps(CRs1, CRs2).
2504
2505compact_otp5186_check_cmdRep(CR, CR) ->
2506    ok;
2507compact_otp5186_check_cmdRep({auditValueReply, AVR1},
2508			     {auditValueReply, AVR2}) ->
2509    compact_otp5186_check_auditReply(AVR1, AVR2);
2510compact_otp5186_check_cmdRep({addReply, AVR1},
2511			     {addReply, AVR2}) ->
2512    compact_otp5186_check_ammsReply(AVR1, AVR2);
2513compact_otp5186_check_cmdRep(CR1, CR2) ->
2514    exit({unexpected_commandReply, CR1, CR2}).
2515
2516compact_otp5186_check_auditReply(AR, AR) ->
2517    ok;
2518compact_otp5186_check_auditReply({auditResult, AR1},
2519				 {auditResult, AR2}) ->
2520    compact_otp5186_check_auditRes(AR1, AR2);
2521compact_otp5186_check_auditReply(AR1, AR2) ->
2522    exit({unexpected_auditReply, AR1, AR2}).
2523
2524compact_otp5186_check_ammsReply(AR, AR) ->
2525    ok;
2526compact_otp5186_check_ammsReply(#'AmmsReply'{terminationID = ID,
2527					     terminationAudit = TA1},
2528				#'AmmsReply'{terminationID = ID,
2529					     terminationAudit = TA2}) ->
2530    %% This is just to simplify the test
2531    F = fun(asn1_NOVALUE) -> [];
2532	   (E) -> E
2533	end,
2534    compact_otp5186_check_termAudit(F(TA1), F(TA2));
2535compact_otp5186_check_ammsReply(AR1, AR2) ->
2536    exit({unexpected_ammsReply, AR1, AR2}).
2537
2538compact_otp5186_check_auditRes(AR, AR) ->
2539    ok;
2540compact_otp5186_check_auditRes(#'AuditResult'{terminationID = ID,
2541					      terminationAuditResult = TAR1},
2542			       #'AuditResult'{terminationID = ID,
2543					      terminationAuditResult = TAR2}) ->
2544    compact_otp5186_check_termAuditRes(TAR1, TAR2);
2545compact_otp5186_check_auditRes(AR1, AR2) ->
2546    exit({unexpected_auditResult, AR1, AR2}).
2547
2548compact_otp5186_check_termAuditRes([], []) ->
2549    ok;
2550%% An empty empty descriptor is removed
2551compact_otp5186_check_termAuditRes([{emptyDescriptors,
2552				     #'AuditDescriptor'{auditToken = asn1_NOVALUE,
2553							auditPropertyToken = asn1_NOVALUE}}|TAR1], []) ->
2554    compact_otp5186_check_termAuditRes(TAR1, []);
2555compact_otp5186_check_termAuditRes(TAR1, []) ->
2556    exit({not_equal, termAuditRes, TAR1, []});
2557%% An empty empty descriptor is removed
2558compact_otp5186_check_termAuditRes([], [{emptyDescriptors,
2559					 #'AuditDescriptor'{auditToken = asn1_NOVALUE,
2560							    auditPropertyToken = asn1_NOVALUE}}|TAR2]) ->
2561    compact_otp5186_check_termAuditRes([], TAR2);
2562compact_otp5186_check_termAuditRes([], TAR2) ->
2563    exit({not_equal, termAuditRes, [], TAR2});
2564compact_otp5186_check_termAuditRes([ARP1|TAR1], [ARP2|TAR2]) ->
2565    compact_otp5186_check_auditRetParm(ARP1, ARP2),
2566    compact_otp5186_check_termAuditRes(TAR1, TAR2).
2567
2568compact_otp5186_check_termAudit([], []) ->
2569    ok;
2570%% An empty empty descriptor is removed
2571compact_otp5186_check_termAudit([{emptyDescriptors,
2572				  #'AuditDescriptor'{auditToken = asn1_NOVALUE,
2573						     auditPropertyToken = asn1_NOVALUE}}|TAR1], []) ->
2574    compact_otp5186_check_termAudit(TAR1, []);
2575compact_otp5186_check_termAudit(TAR1, []) ->
2576    exit({not_equal, termAudit, TAR1, []});
2577%% An empty empty descriptor is removed
2578compact_otp5186_check_termAudit([],
2579				[{emptyDescriptors,
2580				  #'AuditDescriptor'{auditToken = asn1_NOVALUE,
2581						     auditPropertyToken = asn1_NOVALUE}}|TAR2]) ->
2582    compact_otp5186_check_termAudit([], TAR2);
2583compact_otp5186_check_termAudit([], TAR2) ->
2584    exit({not_equal, termAudit, [], TAR2});
2585compact_otp5186_check_termAudit([ARP1|TAR1], [ARP2|TAR2]) ->
2586    compact_otp5186_check_auditRetParm(ARP1, ARP2),
2587    compact_otp5186_check_termAudit(TAR1, TAR2).
2588
2589compact_otp5186_check_auditRetParm(ARP, ARP) ->
2590    ok;
2591compact_otp5186_check_auditRetParm({emptyDescriptors, AD1},
2592				   {emptyDescriptors, AD2}) ->
2593    compact_otp5186_check_auditDesc(AD1, AD2);
2594compact_otp5186_check_auditRetParm(ARP1, ARP2) ->
2595    exit({unexpected_auditRetParm, ARP1, ARP2}).
2596
2597compact_otp5186_check_auditDesc(AD, AD) ->
2598    ok;
2599compact_otp5186_check_auditDesc(#'AuditDescriptor'{auditToken = L1,
2600						   auditPropertyToken = asn1_NOVALUE},
2601				#'AuditDescriptor'{auditToken = L2,
2602						   auditPropertyToken = asn1_NOVALUE}) ->
2603    compact_otp5186_check_auditDesc_auditItems(L1, L2);
2604compact_otp5186_check_auditDesc(#'AuditDescriptor'{auditToken = asn1_NOVALUE,
2605						   auditPropertyToken = APT1},
2606				#'AuditDescriptor'{auditToken = asn1_NOVALUE,
2607						   auditPropertyToken = APT2}) ->
2608    compact_otp5186_check_auditDesc_apt(APT1, APT2);
2609compact_otp5186_check_auditDesc(AD1, AD2) ->
2610    exit({unexpected_auditDesc, AD1, AD2}).
2611
2612compact_otp5186_check_auditDesc_auditItems([], []) ->
2613    ok;
2614compact_otp5186_check_auditDesc_auditItems(AI1, []) ->
2615    exit({not_equal, auditItems, AI1, []});
2616compact_otp5186_check_auditDesc_auditItems([], AI2) ->
2617    exit({not_equal, auditItems, [], AI2});
2618compact_otp5186_check_auditDesc_auditItems([AI1|AIs1], [AI2|AIs2]) ->
2619    compact_otp5186_check_auditDesc_auditItem(AI1, AI2),
2620    compact_otp5186_check_auditDesc_auditItems(AIs1, AIs2).
2621
2622compact_otp5186_check_auditDesc_auditItem(AI, AI) ->
2623    ok;
2624compact_otp5186_check_auditDesc_auditItem(AI1, AI2) ->
2625    exit({not_equal, auditItem, AI1, AI2}).
2626
2627compact_otp5186_check_auditDesc_apt(APT, APT) ->
2628    ok;
2629compact_otp5186_check_auditDesc_apt(APT1, APT2) ->
2630    exit({not_equal, auditPropertyToken, APT1, APT2}).
2631
2632
2633
2634%% --------------------------------------------------------------
2635
2636compact_otp5290_msg01(suite) ->
2637    [];
2638compact_otp5290_msg01(Config) when is_list(Config) ->
2639    d("compact_otp5290_msg01 -> entry", []),
2640    ?ACQUIRE_NODES(1, Config),
2641    compact_otp5290_msg_1(compact_otp5290_msg01(), ok, ok).
2642
2643compact_otp5290_msg02(suite) ->
2644    [];
2645compact_otp5290_msg02(Config) when is_list(Config) ->
2646    d("compact_otp5290_msg02 -> entry", []),
2647    ?ACQUIRE_NODES(1, Config),
2648    compact_otp5290_msg_1(compact_otp5290_msg02(), error, ignore).
2649
2650compact_otp5290_msg_1(M1, DecodeExpect, EncodeExpect) ->
2651    Bin1 = list_to_binary(M1),
2652    case decode_message(megaco_compact_text_encoder, false, [], Bin1) of
2653	{ok, Msg} when DecodeExpect == ok ->
2654 	    io:format(" decoded", []),
2655	    case encode_message(megaco_compact_text_encoder, [], Msg) of
2656		{ok, Bin1} when EncodeExpect == ok ->
2657		    io:format(", encoded - equal:", []),
2658		    ok;
2659		{ok, Bin2} when EncodeExpect == ok ->
2660		    M2 = binary_to_list(Bin2),
2661		    io:format(", encoded - not equal:", []),
2662		    exit({messages_not_equal, Msg, M1, M2});
2663		{ok, Bin3} when EncodeExpect == error ->
2664		    M3 = binary_to_list(Bin3),
2665		    io:format(", unexpected encode:", []),
2666		    exit({unexpected_encode_success, Msg, M3});
2667		_ when EncodeExpect == error ->
2668		    io:format(", encode failed ", []),
2669		    ok
2670	    end;
2671	{ok, Msg} when DecodeExpect == error ->
2672 	    io:format(" decoded", []),
2673	    exit({unexpected_decode_success, Msg});
2674	_Else when DecodeExpect == error ->
2675	    io:format(" decode failed ", []),
2676	    ok;
2677	Else when DecodeExpect == ok ->
2678	    io:format(" decode failed ", []),
2679	    exit({unexpected_decode_result, Else})
2680    end.
2681
2682compact_otp5290_msg01() ->
2683    "!/" ?VERSION_STR " <ml>\nT=12345678{C=*{CA{TP,PR}}}".
2684
2685compact_otp5290_msg02() ->
2686    "!/" ?VERSION_STR " <ml>\nT=12345678{C=*{CA{TP,PR,TP}}}".
2687
2688
2689compact_otp5793_msg01(suite) ->
2690    [];
2691compact_otp5793_msg01(Config) when is_list(Config) ->
2692    d("compact_otp5793_msg01 -> entry", []),
2693    ?ACQUIRE_NODES(1, Config),
2694    compact_otp5793(ok, pretty_otp5793_msg1()).
2695
2696compact_otp5793(Expected, Msg) ->
2697    expect_codec(Expected, megaco_compact_text_encoder, Msg, []).
2698
2699
2700%% --------------------------------------------------------------
2701
2702compact_otp5993_msg01(suite) ->
2703    [];
2704compact_otp5993_msg01(Config) when is_list(Config) ->
2705    d("compact_otp5993_msg01 -> entry", []),
2706    ?ACQUIRE_NODES(1, Config),
2707    compact_otp5993(ok, compact_otp5993_msg01()).
2708
2709compact_otp5993_msg02(suite) ->
2710    [];
2711compact_otp5993_msg02(Config) when is_list(Config) ->
2712    d("compact_otp5993_msg02 -> entry", []),
2713    ?ACQUIRE_NODES(1, Config),
2714    compact_otp5993(ok, compact_otp5993_msg02()).
2715
2716compact_otp5993_msg03(suite) ->
2717    [];
2718compact_otp5993_msg03(Config) when is_list(Config) ->
2719    d("compact_otp5993_msg03 -> entry", []),
2720    ?ACQUIRE_NODES(1, Config),
2721    compact_otp5993(ok, compact_otp5993_msg03()).
2722
2723compact_otp5993(Expected, Msg) ->
2724    expect_codec(Expected, megaco_compact_text_encoder, Msg, []).
2725
2726compact_otp5993_msg01() ->
2727    MT = h221,
2728    T  = #megaco_term_id{id = ?A4444},
2729    TL = [T],
2730    MD = #'MuxDescriptor'{muxType  = MT,
2731			  termList = TL},
2732    compact_otp5993_msg(MD).
2733
2734compact_otp5993_msg02() ->
2735    MT = h223,
2736    T1 = #megaco_term_id{id = ?A4445},
2737    T2 = #megaco_term_id{id = ?A5556},
2738    TL = [T1, T2],
2739    MD = #'MuxDescriptor'{muxType  = MT,
2740			  termList = TL},
2741    compact_otp5993_msg(MD).
2742
2743compact_otp5993_msg(MD) when is_record(MD, 'MuxDescriptor') ->
2744    AmmDesc  = {muxDescriptor, MD},
2745    AmmReq   = #'AmmRequest'{terminationID = [hd(MD#'MuxDescriptor'.termList)],
2746			     descriptors   = [AmmDesc]},
2747    Cmd      = {addReq, AmmReq},
2748    CmdReq   = #'CommandRequest'{command = Cmd},
2749    ActReq   = #'ActionRequest'{contextId       = 5993,
2750				commandRequests = [CmdReq]},
2751    TransReq = #'TransactionRequest'{transactionId = 3995,
2752				     actions       = [ActReq]},
2753    Trans    = {transactionRequest, TransReq},
2754    Body     = {transactions, [Trans]},
2755    Msg      = #'Message'{version = ?VERSION,
2756			  mId     = ?MG1_MID,
2757			  messageBody = Body},
2758    #'MegacoMessage'{mess = Msg}.
2759
2760compact_otp5993_msg03() ->
2761    T1       = #megaco_term_id{id = ?A4445},
2762    T2       = #megaco_term_id{id = ?A5556},
2763    TIDs     = [T1, T2],
2764    AudRep   = {contextAuditResult, TIDs},
2765    CmdRep   = {auditValueReply, AudRep},
2766    ActRep   = #'ActionReply'{contextId    = 5993,
2767			      commandReply = [CmdRep]},
2768    TransRes = {actionReplies, [ActRep]},
2769    TransRep = #'TransactionReply'{transactionId     = 3995,
2770				   transactionResult = TransRes},
2771    Trans    = {transactionReply, TransRep},
2772    Body     = {transactions, [Trans]},
2773    Msg      = #'Message'{version     = ?VERSION,
2774			  mId         = ?MG1_MID,
2775			  messageBody = Body},
2776    #'MegacoMessage'{mess = Msg}.
2777
2778
2779%% --------------------------------------------------------------
2780
2781compact_otp6017_msg01(suite) ->
2782    [];
2783compact_otp6017_msg01(Config) when is_list(Config) ->
2784    d("compact_otp6017_msg01 -> entry", []),
2785    ?ACQUIRE_NODES(1, Config),
2786    ok = compact_otp6017(0),
2787    ok.
2788
2789compact_otp6017_msg02(suite) ->
2790    [];
2791compact_otp6017_msg02(Config) when is_list(Config) ->
2792    d("compact_otp6017_msg02 -> entry", []),
2793    ?ACQUIRE_NODES(1, Config),
2794    ok = compact_otp6017(16#FFFFFFFE),
2795    ok.
2796
2797compact_otp6017_msg03(suite) ->
2798    [];
2799compact_otp6017_msg03(Config) when is_list(Config) ->
2800    d("compact_otp6017_msg03 -> entry", []),
2801    ?ACQUIRE_NODES(1, Config),
2802    ok = compact_otp6017(16#FFFFFFFF),
2803    ok.
2804
2805compact_otp6017(BadCID) ->
2806    M   = compact_otp6017_msg(BadCID),
2807    Bin = list_to_binary(M),
2808    case decode_message(megaco_compact_text_encoder, false, [], Bin) of
2809        {ok, Msg} ->
2810            exit({unexpected_decode_success, {Msg, M}});
2811        {error, Reason} when is_list(Reason) -> % Expected result
2812            case lists:keysearch(reason, 1, Reason) of
2813                {value, {reason, {_Line, _Mod, {bad_ContextID, BadCID}}}} ->
2814		    io:format(" ~w", [BadCID]),
2815                    ok;
2816                {value, {reason, ActualReason}} ->
2817                    exit({unexpected_reason, ActualReason});
2818                false ->
2819                    exit({reason_not_found, Reason})
2820            end;
2821        Crap ->
2822            exit({unexpected_decode_result, Crap})
2823    end.
2824
2825compact_otp6017_msg(CID) when is_integer(CID) ->
2826    "MEGACO/" ?VERSION_STR " MG1 T=12345678{C=" ++
2827        integer_to_list(CID) ++
2828        "{SC=root{SV{MT=RS,RE=901}}}}".
2829
2830
2831%% --------------------------------------------------------------
2832
2833compact_otp7138_msg01(suite) ->
2834    [];
2835compact_otp7138_msg01(Config) when is_list(Config) ->
2836%%     put(dbg, true),
2837%%     put(severity, trc),
2838    d("compact_otp7138_msg01 -> entry", []),
2839    ?ACQUIRE_NODES(1, Config),
2840    Msg = compact_otp7138_msg01(),
2841    EC  = [],
2842    ok = compact_otp7138(EC, Msg),
2843    ok.
2844
2845compact_otp7138_msg02(suite) ->
2846    [];
2847compact_otp7138_msg02(Config) when is_list(Config) ->
2848%%     put(dbg, true),
2849%%     put(severity, trc),
2850    d("compact_otp7138_msg02 -> entry", []),
2851    ?ACQUIRE_NODES(1, Config),
2852    Msg = compact_otp7138_msg02(),
2853    EC  = [],
2854    ok = compact_otp7138(EC, Msg),
2855    ok.
2856
2857compact_otp7138_msg01() ->
2858    <<"!/2 <gw>\nT=1111{C=1{N=mgw2dev1/1{OE=16777985{ctyp/dtone{dtt=CT}}}}}">>.
2859
2860compact_otp7138_msg02() ->
2861    <<"!/2 <gw>\nT=1111{C=1{N=mgw2dev1/1{OE=16777985{ctyp/dtone{dtt=\"CT\"}}}}}">>.
2862
2863compact_otp7138(EC, BinMsg) ->
2864    d("compact_otp7138 -> "
2865      "~n   ~p", [binary_to_list(BinMsg)]),
2866    Codec = megaco_compact_text_encoder,
2867    case decode_message(Codec, false, EC, BinMsg) of
2868	{ok, Msg} ->
2869	    case encode_message(Codec, EC, Msg) of
2870		{ok, BinMsg} ->
2871		    d("compact_otp7138 -> encode successfull: "
2872		      "~n   ~p", [binary_to_list(BinMsg)]),
2873		    ok;
2874		{ok, BinMsg2} ->
2875		    d("compact_otp7138 -> encode successfull but result differ: "
2876		      "~n   ~p", [binary_to_list(BinMsg2)]),
2877		    ok;
2878		{error, Reason} ->
2879		    e("encode failed: ~p", [Reason]),
2880		    {error, Reason}
2881	    end;
2882	{error, Reason} ->
2883	    e("decode failed: ~p", [Reason]),
2884	    {error, Reason}
2885    end.
2886
2887
2888compact_otp7457_msg01(suite) ->
2889    [];
2890compact_otp7457_msg01(Config) when is_list(Config) ->
2891    put(dbg, true),
2892    put(severity, trc),
2893    d("compact_otp7457_msg01 -> entry", []),
2894    ?ACQUIRE_NODES(1, Config),
2895    Msg = compact_otp7457_msg01(),
2896    EC  = [],
2897    ok = compact_otp7457(EC, Msg),
2898    ok.
2899
2900compact_otp7457_msg02(suite) ->
2901    [];
2902compact_otp7457_msg02(Config) when is_list(Config) ->
2903    put(dbg, true),
2904    put(severity, trc),
2905    d("compact_otp7457_msg02 -> entry", []),
2906    ?ACQUIRE_NODES(1, Config),
2907    Msg = compact_otp7457_msg02(),
2908    EC  = [],
2909    ok = compact_otp7457(EC, Msg),
2910    ok.
2911
2912compact_otp7457_msg03(suite) ->
2913    [];
2914compact_otp7457_msg03(Config) when is_list(Config) ->
2915    put(dbg, true),
2916    put(severity, trc),
2917    d("compact_otp7457_msg03 -> entry", []),
2918    ?ACQUIRE_NODES(1, Config),
2919    Msg = compact_otp7457_msg03(),
2920    EC  = [],
2921    ok = compact_otp7457(EC, Msg),
2922    ok.
2923
2924compact_otp7457_msg01() ->
2925    <<"!/2 <mg1>\nT=15{C=-{SC=tdm12/1/1/*{SV{MT=RS,RE=900}}}}\n">>.
2926
2927compact_otp7457_msg02() ->
2928    <<"!/2 <mg1>\nT=15{C=-{O-SC=tdm12/1/1/*{SV{MT=RS,RE=900}}}}\n">>.
2929
2930compact_otp7457_msg03() ->
2931    <<"!/2 <mg1>\nT=15{C=-{W-SC=tdm12/1/1/*{SV{MT=RS,RE=900}}}}\n">>.
2932
2933compact_otp7457(EC, BinMsg) ->
2934    d("compact_otp7457 -> "
2935      "~n   ~p", [binary_to_list(BinMsg)]),
2936    Codec = megaco_compact_text_encoder,
2937    case decode_message(Codec, false, EC, BinMsg) of
2938	{ok, Msg} ->
2939	    case encode_message(Codec, EC, Msg) of
2940		{ok, BinMsg} ->
2941		    d("compact_otp7457 -> encode successfull: "
2942		      "~n   ~p", [binary_to_list(BinMsg)]),
2943		    ok;
2944		{ok, BinMsg2} ->
2945		    d("compact_otp7457 -> "
2946		      "encode successfull but result differ: "
2947		      "~n   ~p", [binary_to_list(BinMsg2)]),
2948		    ok;
2949		{error, Reason} ->
2950		    e("encode failed: ~p", [Reason]),
2951		    {error, Reason}
2952	    end;
2953	{error, Reason} ->
2954	    e("decode failed: ~p", [Reason]),
2955	    {error, Reason}
2956    end.
2957
2958compact_otp7534_msg01(suite) ->
2959    [];
2960compact_otp7534_msg01(Config) when is_list(Config) ->
2961    put(dbg, true),
2962    put(severity, trc),
2963    d("compact_otp7534_msg01 -> entry", []),
2964    Msg = otp7534_msg01(),
2965    compact_otp7534([], Msg).
2966
2967
2968compact_otp7576_msg01(suite) ->
2969    [];
2970compact_otp7576_msg01(Config) when is_list(Config) ->
2971%%     put(dbg, true),
2972%%     put(severity, trc),
2973    d("compact_otp7576_msg01 -> entry", []),
2974    ?ACQUIRE_NODES(1, Config),
2975    Msg = compact_otp7576_msg01(),
2976    EC  = [],
2977    ok = compact_otp7576(EC, Msg),
2978    ok.
2979
2980compact_otp7576_msg01() ->
2981    M = "!/"
2982	?VERSION_STR
2983	"[130.100.144.37]:2944\nT=10032{C=${tp{*,*,is,st=1},pr=6,a=rtp/2/${m{st=1{o{mo=so,rv=ON},l{
2984v=0
2985c=IN IP4 $
2986m=audio $ RTP/AVP 0
2987b=AS:64
2988a=rtpmap:0 PCMU/8000
2989}}},e=1{G/CAUSE}},a=rtp/2/${m{st=1{o{mo=rc,rv=ON},l{
2990v=0
2991c=IN IP4 $
2992m=audio $ RTP/AVP 0
2993b=AS:64
2994a=rtpmap:0 PCMU/8000
2995},r{
2996v=0
2997c=IN IP4 130.100.126.77
2998m=audio 8014 RTP/AVP 0
2999b=AS:64
3000a=rtpmap:0 PCMU/8000
3001}}},e=1{G/CAUSE}}}}",
3002    list_to_binary(M).
3003
3004compact_otp7576(EC, BinMsg) ->
3005    d("compact_otp7576 -> "
3006      "~n   ~p", [binary_to_list(BinMsg)]),
3007    Codec = megaco_compact_text_encoder,
3008    case decode_message(Codec, false, EC, BinMsg) of
3009	{ok, Msg} ->
3010	    case encode_message(Codec, EC, Msg) of
3011		{ok, BinMsg} ->
3012		    d("compact_otp7138 -> encode successfull: "
3013		      "~n   ~p", [binary_to_list(BinMsg)]),
3014		    ok;
3015		{ok, BinMsg2} ->
3016		    d("compact_otp7138 -> encode successfull but result differ: "
3017		      "~n   ~p", [binary_to_list(BinMsg2)]),
3018                    case decode_message(Codec, false, EC, BinMsg2) of
3019			{ok, Msg} ->
3020			    d("compact_otp7138 -> "
3021			      "extra verification decode ok", []),
3022			    ok;
3023			{ok, Msg2} ->
3024			    e("verification decode generated other message: "
3025			      "~n   Msg:  ~p"
3026			      "~n   Msg2: ~p", [Msg, Msg2]),
3027			    {error, {verification_decode, Msg, Msg2}}
3028		    end;
3029		{error, Reason} ->
3030		    e("encode failed: ~p", [Reason]),
3031		    {error, Reason}
3032	    end;
3033	{error, Reason} ->
3034	    e("decode failed: ~p", [Reason]),
3035	    {error, Reason}
3036    end.
3037
3038
3039%% --------------------------------------------------------------
3040%%
3041
3042compact_otp7671_msg01(suite) ->
3043    [];
3044compact_otp7671_msg01(Config) when is_list(Config) ->
3045    put(severity, trc),
3046    put(dbg,      true),
3047    d("compact_otp7671_msg01 -> entry", []),
3048    %% ?ACQUIRE_NODES(1, Config),
3049    ok = compact_otp7671( compact_otp7671_msg01(), [] ),
3050    erase(dbg),
3051    erase(severity),
3052    ok.
3053
3054compact_otp7671(Msg, Conf) ->
3055    compact_otp7671(Msg, Conf, ok).
3056
3057compact_otp7671(Msg, Conf, ExpectedEncode) ->
3058    compact_otp7671(Msg, Conf, ExpectedEncode, ok).
3059
3060compact_otp7671(Msg, Conf, ExpectedEncode, ExpectedDecode) ->
3061    otp7671(Msg, megaco_compact_text_encoder, Conf,
3062            ExpectedEncode, ExpectedDecode).
3063
3064%% "!/" ?VERSION_STR " <ml>\nT=172047781{C=-{MF=root{DM=DmName}}}",
3065compact_otp7671_msg01() ->
3066    pretty_otp7671_msg01().
3067
3068
3069
3070%% --------------------------------------------------------------
3071%%
3072compact_otp16818_msg01(suite) ->
3073    [];
3074compact_otp16818_msg01(Config) when is_list(Config) ->
3075    d("compact_otp16818_msg01 -> entry", []),
3076    ok = compact_otp16818( compact_otp16818_msg01() ),
3077    ok.
3078
3079compact_otp16818_msg01() ->
3080    compact_otp16818_msg("a").
3081
3082
3083%% --
3084
3085compact_otp16818_msg02(suite) ->
3086    [];
3087compact_otp16818_msg02(Config) when is_list(Config) ->
3088    d("compact_otp16818_msg02 -> entry", []),
3089    ok = compact_otp16818( compact_otp16818_msg02() ),
3090    ok.
3091
3092compact_otp16818_msg02() ->
3093    compact_otp16818_msg("b").
3094
3095
3096%% --
3097
3098compact_otp16818_msg03(suite) ->
3099    [];
3100compact_otp16818_msg03(Config) when is_list(Config) ->
3101    d("compact_otp16818_msg03 -> entry", []),
3102    ok = compact_otp16818( compact_otp16818_msg03() ),
3103    ok.
3104
3105compact_otp16818_msg03() ->
3106    compact_otp16818_msg("c").
3107
3108
3109%% --
3110
3111compact_otp16818_msg04(suite) ->
3112    [];
3113compact_otp16818_msg04(Config) when is_list(Config) ->
3114    d("compact_otp16818_msg04 -> entry", []),
3115    ok = compact_otp16818( compact_otp16818_msg04() ),
3116    ok.
3117
3118compact_otp16818_msg04() ->
3119    compact_otp16818_msg("d").
3120
3121
3122%% --
3123
3124compact_otp16818_msg05(suite) ->
3125    [];
3126compact_otp16818_msg05(Config) when is_list(Config) ->
3127    d("compact_otp16818_msg05 -> entry", []),
3128    ok = compact_otp16818( compact_otp16818_msg05() ),
3129    ok.
3130
3131compact_otp16818_msg05() ->
3132    compact_otp16818_msg("e").
3133
3134
3135%% --
3136
3137compact_otp16818_msg06(suite) ->
3138    [];
3139compact_otp16818_msg06(Config) when is_list(Config) ->
3140    d("compact_otp16818_msg06 -> entry", []),
3141    ok = compact_otp16818( compact_otp16818_msg06() ),
3142    ok.
3143
3144compact_otp16818_msg06() ->
3145    compact_otp16818_msg("f").
3146
3147
3148%% --
3149
3150compact_otp16818_msg11(suite) ->
3151    [];
3152compact_otp16818_msg11(Config) when is_list(Config) ->
3153    d("compact_otp16818_msg11 -> entry", []),
3154    ok = compact_otp16818( compact_otp16818_msg11() ),
3155    ok.
3156
3157compact_otp16818_msg11() ->
3158    compact_otp16818_msg("000a").
3159
3160
3161%% --
3162
3163compact_otp16818_msg12(suite) ->
3164    [];
3165compact_otp16818_msg12(Config) when is_list(Config) ->
3166    d("compact_otp16818_msg12 -> entry", []),
3167    ok = compact_otp16818( compact_otp16818_msg12() ),
3168    ok.
3169
3170compact_otp16818_msg12() ->
3171    compact_otp16818_msg("000b").
3172
3173
3174%% --
3175
3176compact_otp16818_msg13(suite) ->
3177    [];
3178compact_otp16818_msg13(Config) when is_list(Config) ->
3179    d("compact_otp16818_msg13 -> entry", []),
3180    ok = compact_otp16818( compact_otp16818_msg13() ),
3181    ok.
3182
3183compact_otp16818_msg13() ->
3184    compact_otp16818_msg("000c").
3185
3186
3187%% --
3188
3189compact_otp16818_msg14(suite) ->
3190    [];
3191compact_otp16818_msg14(Config) when is_list(Config) ->
3192    d("compact_otp16818_msg14 -> entry", []),
3193    ok = compact_otp16818( compact_otp16818_msg14() ),
3194    ok.
3195
3196compact_otp16818_msg14() ->
3197    compact_otp16818_msg("000d").
3198
3199
3200%% --
3201
3202compact_otp16818_msg15(suite) ->
3203    [];
3204compact_otp16818_msg15(Config) when is_list(Config) ->
3205    d("compact_otp16818_msg15 -> entry", []),
3206    ok = compact_otp16818( compact_otp16818_msg15() ),
3207    ok.
3208
3209compact_otp16818_msg15() ->
3210    compact_otp16818_msg("000e").
3211
3212
3213%% --
3214
3215compact_otp16818_msg16(suite) ->
3216    [];
3217compact_otp16818_msg16(Config) when is_list(Config) ->
3218    d("compact_otp16818_msg16 -> entry", []),
3219    ok = compact_otp16818( compact_otp16818_msg16() ),
3220    ok.
3221
3222compact_otp16818_msg16() ->
3223    compact_otp16818_msg("000f").
3224
3225
3226%% --
3227
3228compact_otp16818_msg21(suite) ->
3229    [];
3230compact_otp16818_msg21(Config) when is_list(Config) ->
3231    d("compact_otp16818_msg21 -> entry", []),
3232    ok = compact_otp16818( compact_otp16818_msg21() ),
3233    ok.
3234
3235compact_otp16818_msg21() ->
3236    compact_otp16818_msg("0a12").
3237
3238
3239%% --
3240
3241compact_otp16818_msg22(suite) ->
3242    [];
3243compact_otp16818_msg22(Config) when is_list(Config) ->
3244    d("compact_otp16818_msg22 -> entry", []),
3245    ok = compact_otp16818( compact_otp16818_msg22() ),
3246    ok.
3247
3248compact_otp16818_msg22() ->
3249    compact_otp16818_msg("0b12").
3250
3251
3252%% --
3253
3254compact_otp16818_msg23(suite) ->
3255    [];
3256compact_otp16818_msg23(Config) when is_list(Config) ->
3257    d("compact_otp16818_msg23 -> entry", []),
3258    ok = compact_otp16818( compact_otp16818_msg23() ),
3259    ok.
3260
3261compact_otp16818_msg23() ->
3262    compact_otp16818_msg("0c12").
3263
3264
3265%% --
3266
3267compact_otp16818_msg24(suite) ->
3268    [];
3269compact_otp16818_msg24(Config) when is_list(Config) ->
3270    d("compact_otp16818_msg24 -> entry", []),
3271    ok = compact_otp16818( compact_otp16818_msg24() ),
3272    ok.
3273
3274compact_otp16818_msg24() ->
3275    compact_otp16818_msg("0d12").
3276
3277
3278%% --
3279
3280compact_otp16818_msg25(suite) ->
3281    [];
3282compact_otp16818_msg25(Config) when is_list(Config) ->
3283    d("compact_otp16818_msg25 -> entry", []),
3284    ok = compact_otp16818( compact_otp16818_msg25() ),
3285    ok.
3286
3287compact_otp16818_msg25() ->
3288    compact_otp16818_msg("0e12").
3289
3290
3291%% --
3292
3293compact_otp16818_msg26(suite) ->
3294    [];
3295compact_otp16818_msg26(Config) when is_list(Config) ->
3296    d("compact_otp16818_msg26 -> entry", []),
3297    ok = compact_otp16818( compact_otp16818_msg26() ),
3298    ok.
3299
3300compact_otp16818_msg26() ->
3301    compact_otp16818_msg("0f12").
3302
3303
3304%% --
3305
3306compact_otp16818_msg31(suite) ->
3307    [];
3308compact_otp16818_msg31(Config) when is_list(Config) ->
3309    d("compact_otp16818_msg31 -> entry", []),
3310    ok = compact_otp16818( compact_otp16818_msg31() ),
3311    ok.
3312
3313compact_otp16818_msg31() ->
3314    compact_otp16818_msg("a123").
3315
3316
3317%% --
3318
3319compact_otp16818_msg32(suite) ->
3320    [];
3321compact_otp16818_msg32(Config) when is_list(Config) ->
3322    d("compact_otp16818_msg32 -> entry", []),
3323    ok = compact_otp16818( compact_otp16818_msg32() ),
3324    ok.
3325
3326compact_otp16818_msg32() ->
3327    compact_otp16818_msg("b123").
3328
3329
3330%% --
3331
3332compact_otp16818_msg33(suite) ->
3333    [];
3334compact_otp16818_msg33(Config) when is_list(Config) ->
3335    d("compact_otp16818_msg33 -> entry", []),
3336    ok = compact_otp16818( compact_otp16818_msg33() ),
3337    ok.
3338
3339compact_otp16818_msg33() ->
3340    compact_otp16818_msg("c123").
3341
3342
3343%% --
3344
3345compact_otp16818_msg34(suite) ->
3346    [];
3347compact_otp16818_msg34(Config) when is_list(Config) ->
3348    d("compact_otp16818_msg34 -> entry", []),
3349    ok = compact_otp16818( compact_otp16818_msg34() ),
3350    ok.
3351
3352compact_otp16818_msg34() ->
3353    compact_otp16818_msg("d123").
3354
3355
3356%% --
3357
3358compact_otp16818_msg35(suite) ->
3359    [];
3360compact_otp16818_msg35(Config) when is_list(Config) ->
3361    d("compact_otp16818_msg35 -> entry", []),
3362    ok = compact_otp16818( compact_otp16818_msg35() ),
3363    ok.
3364
3365compact_otp16818_msg35() ->
3366    compact_otp16818_msg("e123").
3367
3368
3369%% --
3370
3371compact_otp16818_msg36(suite) ->
3372    [];
3373compact_otp16818_msg36(Config) when is_list(Config) ->
3374    d("compact_otp16818_msg36 -> entry", []),
3375    ok = compact_otp16818( compact_otp16818_msg36() ),
3376    ok.
3377
3378compact_otp16818_msg36() ->
3379    compact_otp16818_msg("f123").
3380
3381
3382%% -----
3383
3384compact_otp16818( Msg ) ->
3385    Bin = erlang:list_to_binary(Msg),
3386    try megaco_compact_text_encoder:decode_message([], dynamic, Bin) of
3387        {ok, _} ->
3388            ok;
3389        {error, _} = ERROR ->
3390            ERROR
3391     catch
3392        C:E:S ->
3393            {error, {C, E, S}}
3394    end.
3395
3396compact_otp16818_msg(X) when is_list(X) ->
3397    "!/2 [2409:8050:5005:1243:1011::" ++ X ++
3398        "] T=2523{C=-{SC=ROOT{SV{MT=RS,RE=901,PF=ETSI_BGF/2,V=3}}}}".
3399
3400
3401%% ==============================================================
3402%%
3403%% F l e x   C o m p a c t   T e s t c a s e s
3404%%
3405
3406flex_compact_otp7138_msg01(suite) ->
3407    [];
3408flex_compact_otp7138_msg01(Config) when is_list(Config) ->
3409    %%     put(dbg, true),
3410    %%     put(severity, trc),
3411    d("flex_compact_otp7138_msg01 -> entry", []),
3412    Msg  = compact_otp7138_msg01(),
3413    Conf = flex_scanner_conf(Config),
3414    compact_otp7138([Conf], Msg).
3415
3416flex_compact_otp7138_msg02(suite) ->
3417    [];
3418flex_compact_otp7138_msg02(Config) when is_list(Config) ->
3419    %%     put(dbg, true),
3420    %%     put(severity, trc),
3421    d("flex_compact_otp7138_msg02 -> entry", []),
3422    Msg  = compact_otp7138_msg02(),
3423    Conf = flex_scanner_conf(Config),
3424    compact_otp7138([Conf], Msg).
3425
3426
3427flex_compact_otp7431_msg01(suite) ->
3428    [];
3429flex_compact_otp7431_msg01(Config) when is_list(Config) ->
3430    %% put(severity,trc),
3431    %% put(dbg,true),
3432    d("flex_comppact_otp7431_msg01 -> entry", []),
3433    Conf = flex_scanner_conf(Config),
3434    flex_compact_otp7431(ok, flex_compact_otp7431_msg1(), [Conf]).
3435
3436flex_compact_otp7431_msg02(suite) ->
3437    [];
3438flex_compact_otp7431_msg02(Config) when is_list(Config) ->
3439    %% put(severity,trc),
3440    %% put(dbg,true),
3441    d("flex_comppact_otp7431_msg02 -> entry", []),
3442    Conf = flex_scanner_conf(Config),
3443    flex_compact_otp7431(error, flex_compact_otp7431_msg2(), [Conf]).
3444
3445flex_compact_otp7431_msg03(suite) ->
3446    [];
3447flex_compact_otp7431_msg03(Config) when is_list(Config) ->
3448    %% put(severity,trc),
3449    %% put(dbg,true),
3450    d("flex_comppact_otp7431_msg03 -> entry", []),
3451    Conf = flex_scanner_conf(Config),
3452    flex_compact_otp7431(error, flex_compact_otp7431_msg3(), [Conf]).
3453
3454flex_compact_otp7431_msg04(suite) ->
3455    [];
3456flex_compact_otp7431_msg04(Config) when is_list(Config) ->
3457    %% put(severity,trc),
3458    %% put(dbg,true),
3459    d("flex_comppact_otp7431_msg04 -> entry", []),
3460    Conf = flex_scanner_conf(Config),
3461    flex_compact_otp7431(error, flex_compact_otp7431_msg4(), [Conf]).
3462
3463flex_compact_otp7431_msg05(suite) ->
3464    [];
3465flex_compact_otp7431_msg05(Config) when is_list(Config) ->
3466    %% put(severity,trc),
3467    %% put(dbg,true),
3468    d("flex_comppact_otp7431_msg05 -> entry", []),
3469    Conf = flex_scanner_conf(Config),
3470    flex_compact_otp7431(error, flex_compact_otp7431_msg5(), [Conf]).
3471
3472flex_compact_otp7431_msg06(suite) ->
3473    [];
3474flex_compact_otp7431_msg06(Config) when is_list(Config) ->
3475    %% put(severity,trc),
3476    %% put(dbg,true),
3477    d("flex_comppact_otp7431_msg06 -> entry", []),
3478    Conf = flex_scanner_conf(Config),
3479    flex_compact_otp7431(error, flex_compact_otp7431_msg6(), [Conf]).
3480
3481flex_compact_otp7431_msg07(suite) ->
3482    [];
3483flex_compact_otp7431_msg07(Config) when is_list(Config) ->
3484    %% put(severity,trc),
3485    %% put(dbg,true),
3486    d("flex_comppact_otp7431_msg07 -> entry", []),
3487    Conf = flex_scanner_conf(Config),
3488    flex_compact_otp7431(error, flex_compact_otp7431_msg7(), [Conf]).
3489
3490
3491flex_compact_otp7431(Expected, Msg, Conf) ->
3492    otp7431(Expected, megaco_compact_text_encoder, Msg, Conf).
3493
3494flex_compact_otp7431_msg1() ->
3495    "!/1 [124.124.124.222]:55555
3496P=10003{C=2000{A=a4444,A=a4445{M{ST=1{L{
3497v=0
3498o=- 2890844526 2890842807 IN IP4 124.124.124.222
3499s=-
3500t= 0 0
3501c=IN IP4 124.124.124.222
3502m=audio 2222 RTP/AVP 4
3503a=ptime:30
3504a=recvonly
3505}}}}}}".
3506
3507flex_compact_otp7431_msg2() ->
3508    "!/1 [124.124.124.222]:55555
3509P=10003{C=2000{A=a4444,A=a4445{M{ST=1{L{
3510v=0
3511o=- 2890844526 2890842807 IN IP4 124.124.124.222
3512s=-
3513t= 0 0
3514c=IN IP4 124.124.124.222
3515m=audio 2222 RTP/AVP 4
3516a=ptime:30
3517a=     }
3518}}}}}".
3519
3520
3521flex_compact_otp7431_msg3() ->
3522    "!/1 [124.124.124.222]:55555
3523P=10003{C=2000{A=a4444,A=a4445{M{ST=1{L{
3524v=0
3525o=- 2890844526 2890842807 IN IP4 124.124.124.222
3526s=-
3527t= 0 0
3528c=IN IP4 124.124.124.222
3529m=audio 2222 RTP/AVP 4
3530a=ptime:30
3531a     }
3532}}}}}".
3533
3534
3535flex_compact_otp7431_msg4() ->
3536    "!/1 [124.124.124.222]:55555
3537P=10003{C=2000{A=a4444,A=a4445{M{ST=1{L{
3538v=0
3539o=- 2890844526 2890842807 IN IP4 124.124.124.222
3540s=-
3541t= 0 0
3542c=IN IP4 124.124.124.222
3543m=audio 2222 RTP/AVP 4
3544a=ptime:30
3545a}
3546}}}}}".
3547
3548
3549flex_compact_otp7431_msg5() ->
3550    "!/1 [124.124.124.222]:55555
3551P=10003{C=2000{A=a4444,A=a4445{M{ST=1{L{
3552v=       }
3553}}}}}".
3554
3555
3556flex_compact_otp7431_msg6() ->
3557    "!/1 [124.124.124.222]:55555
3558P=10003{C=2000{A=a4444,A=a4445{M{ST=1{L{
3559v       }
3560}}}}}".
3561
3562flex_compact_otp7431_msg7() ->
3563    "!/1 [124.124.124.222]:55555
3564P=10003{C=2000{A=a4444,A=a4445{M{ST=1{L{
3565v}
3566}}}}}".
3567
3568flex_compact_otp7457_msg01(suite) ->
3569    [];
3570flex_compact_otp7457_msg01(Config) when is_list(Config) ->
3571    put(dbg, true),
3572    put(severity, trc),
3573    d("flex_compact_otp7457_msg01 -> entry", []),
3574    Msg  = compact_otp7457_msg01(),
3575    Conf = flex_scanner_conf(Config),
3576    compact_otp7457([Conf], Msg).
3577
3578flex_compact_otp7457_msg02(suite) ->
3579    [];
3580flex_compact_otp7457_msg02(Config) when is_list(Config) ->
3581    put(dbg, true),
3582    put(severity, trc),
3583    d("flex_compact_otp7457_msg02 -> entry", []),
3584    Msg  = compact_otp7457_msg02(),
3585    Conf = flex_scanner_conf(Config),
3586    compact_otp7457([Conf], Msg).
3587
3588flex_compact_otp7457_msg03(suite) ->
3589    [];
3590flex_compact_otp7457_msg03(Config) when is_list(Config) ->
3591    put(dbg, true),
3592    put(severity, trc),
3593    d("flex_compact_otp7457_msg03 -> entry", []),
3594    Msg  = compact_otp7457_msg03(),
3595    Conf = flex_scanner_conf(Config),
3596    compact_otp7457([Conf], Msg).
3597
3598flex_compact_otp7534_msg01(suite) ->
3599    [];
3600flex_compact_otp7534_msg01(Config) when is_list(Config) ->
3601    put(dbg, true),
3602    put(severity, trc),
3603    d("flex_compact_otp7534_msg01 -> entry", []),
3604    Msg  = otp7534_msg01(),
3605    Conf = flex_scanner_conf(Config),
3606    compact_otp7534([Conf], Msg).
3607
3608otp7534_msg01() ->
3609    <<"!/2 bgwch3_1\nP=62916991{C=-{AV=root{M{TS{ipra/ar=[interconnect,interconnect1,internal],SI=IV}},PG{root-2,ocp-1,it-1,nt-1,rtp-1,gm-1,ds-1,tman-1,xnq-1}}}}">>.
3610
3611compact_otp7534(EC, BinMsg) ->
3612    Codec = megaco_compact_text_encoder,
3613    otp7534(Codec, EC, BinMsg).
3614
3615otp7534(Codec, EC, BinMsg) ->
3616    d("otp7534 -> "
3617      "~n   Codec: ~p"
3618      "~n   ~p", [Codec, binary_to_list(BinMsg)]),
3619    case decode_message(Codec, false, EC, BinMsg) of
3620	{ok, Msg} ->
3621	    case encode_message(Codec, EC, Msg) of
3622		{ok, BinMsg} ->
3623		    d("otp7457 -> encode successfull: "
3624		      "~n   ~p", [binary_to_list(BinMsg)]),
3625		    ok;
3626		{ok, BinMsg2} ->
3627		    d("otp7457 -> "
3628		      "encode successfull but result differ: "
3629		      "~n   ~p", [binary_to_list(BinMsg2)]),
3630		    ok;
3631		{error, Reason} ->
3632		    e("encode failed: ~p", [Reason]),
3633		    {error, Reason}
3634	    end;
3635	{error, Reason} ->
3636	    e("decode failed: ~p", [Reason]),
3637	    {error, Reason}
3638    end.
3639
3640
3641flex_compact_otp7573_msg01(suite) ->
3642    [];
3643flex_compact_otp7573_msg01(Config) when is_list(Config) ->
3644    put(dbg, true),
3645    put(severity, trc),
3646    d("flex_compact_otp7573_msg01 -> entry", []),
3647    Msg  = otp7573_msg01(),
3648    Conf = flex_scanner_conf(Config),
3649    compact_otp7573([Conf], Msg).
3650
3651otp7573_msg01() ->
3652    <<"!/2 <aa>\nP=37775561{C=-{AV=root{M{TS{root/maxnumberofcontexts=16000,root/maxterminationspercontext=2,root/normalmgexecutiontime=3000,root/normalmgcexecutiontime=3000,root/mgprovisionalresponsetimervalue=2000,root/mgcprovisionalresponsetimervalue=2000,root/mgcoriginatedpendinglimit=5,root/mgoriginatedpendinglimit=5,ipra/ar=[\"\"],SI=IV}},PG{root-2,ocp-1,it-1,nt-1,rtp-1,gm-1,ds-1,tman-1,xnq-1,ipra-1}}}}">>.
3653
3654compact_otp7573(EC, BinMsg) ->
3655    Codec = megaco_compact_text_encoder,
3656    otp7573(Codec, EC, BinMsg).
3657
3658otp7573(Codec, EC, BinMsg) ->
3659    d("otp7573 -> "
3660      "~n   Codec: ~p"
3661      "~n   ~p", [Codec, binary_to_list(BinMsg)]),
3662    case decode_message(Codec, false, EC, BinMsg) of
3663	{ok, Msg} ->
3664	    case encode_message(Codec, EC, Msg) of
3665		{ok, BinMsg} ->
3666		    d("otp7573 -> encode successfull: "
3667		      "~n   ~p", [binary_to_list(BinMsg)]),
3668		    ok;
3669		{ok, BinMsg2} ->
3670		    d("otp7573 -> "
3671		      "encode successfull but result differ: "
3672		      "~n   ~p", [binary_to_list(BinMsg2)]),
3673		    ok;
3674		{error, Reason} ->
3675		    e("encode failed: ~p", [Reason]),
3676		    {error, Reason}
3677	    end;
3678	{error, Reason} ->
3679	    e("decode failed: ~p", [Reason]),
3680	    {error, Reason}
3681    end.
3682
3683
3684flex_compact_otp7576_msg01(suite) ->
3685    [];
3686flex_compact_otp7576_msg01(Config) when is_list(Config) ->
3687    %%     put(dbg, true),
3688    %%     put(severity, trc),
3689    d("flex_compact_otp7576_msg01 -> entry", []),
3690    Msg  = compact_otp7576_msg01(),
3691    Conf = flex_scanner_conf(Config),
3692    compact_otp7576([Conf], Msg).
3693
3694
3695%% killer_42_original
3696flex_compact_otp10998_msg01() ->
3697    <<"!/2 stofmg0
3698P=25165898{C=34227581{AV=r01/03/01/38/22{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3699v=0
3700c=TN RFC2543 -
3701m=audio - TDM -
3702}}}},C=34227613{AV=r01/03/01/38/12{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3703v=0
3704c=TN RFC2543 -
3705m=audio - TDM -
3706}}}},C=34227744{AV=r01/03/01/38/11{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3707v=0
3708c=TN RFC2543 -
3709m=audio - TDM -
3710}}}},C=34227755{AV=r01/03/01/38/2{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3711v=0
3712c=TN RFC2543 -
3713m=audio - TDM -
3714}}}},C=34227768{AV=r01/03/01/38/14{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3715v=0
3716c=TN RFC2543 -
3717m=audio - TDM -
3718}}}},C=34227774{AV=r01/03/01/38/15{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3719v=0
3720c=TN RFC2543 -
3721m=audio - TDM -
3722}}}},C=34227775{AV=r01/03/01/38/16{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3723v=0
3724c=TN RFC2543 -
3725m=audio - TDM -
3726}}}},C=34323119{AV=r01/03/01/38/9{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3727v=0
3728c=TN RFC2543 -
3729m=audio - TDM -
3730}}}},C=34323122{AV=r01/03/01/38/7{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3731v=0
3732c=TN RFC2543 -
3733m=audio - TDM -
3734}}}},C=34323156{AV=r01/03/01/38/8{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3735v=0
3736c=TN RFC2543 -
3737m=audio - TDM -
3738}}}},C=34323260{AV=r01/03/01/38/13{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3739v=0
3740c=TN RFC2543 -
3741m=audio - TDM -
3742}}}},C=34323272{AV=r01/03/01/38/30{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3743v=0
3744c=TN RFC2543 -
3745m=audio - TDM -
3746}}}},C=34323273{AV=r01/03/01/38/29{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3747v=0
3748c=TN RFC2543 -
3749m=audio - TDM -
3750}}}},C=34323275{AV=r01/03/01/38/25{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3751v=0
3752c=TN RFC2543 -
3753m=audio - TDM -
3754}}}},C=34323276{AV=r01/03/01/38/28{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3755v=0
3756c=TN RFC2543 -
3757m=audio - TDM -
3758}}}},C=34323279{AV=r01/03/01/38/26{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3759v=0
3760c=TN RFC2543 -
3761m=audio - TDM -
3762}}}},C=34323280{AV=r01/03/01/38/24{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3763v=0
3764c=TN RFC2543 -
3765m=audio - TDM -
3766}}}},C=34323281{AV=r01/03/01/38/27{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3767v=0
3768c=TN RFC2543 -
3769m=audio - TDM -
3770}}}},C=34323284{AV=r01/03/01/38/23{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3771v=0
3772c=TN RFC2543 -
3773m=audio - TDM -
3774}}}},C=34129764{AV=r01/03/01/55/31{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3775v=0
3776c=TN RFC2543 -
3777m=audio - TDM -
3778}}}},C=34227463{AV=r01/03/01/55/26{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3779v=0
3780c=TN RFC2543 -
3781m=audio - TDM -
3782}}}},C=34227472{AV=r01/03/01/55/22{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3783v=0
3784c=TN RFC2543 -
3785m=audio - TDM -
3786}}}},C=34227484{AV=r01/03/01/55/16{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3787v=0
3788c=TN RFC2543 -
3789m=audio - TDM -
3790}}}},C=34227555{AV=r01/03/01/55/5{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3791v=0
3792c=TN RFC2543 -
3793m=audio - TDM -
3794}}}},C=34227556{AV=r01/03/01/55/14{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3795v=0
3796c=TN RFC2543 -
3797m=audio - TDM -
3798}}}},C=34227557{AV=r01/03/01/55/10{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3799v=0
3800c=TN RFC2543 -
3801m=audio - TDM -
3802}}}},C=34227563{AV=r01/03/01/55/7{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3803v=0
3804c=TN RFC2543 -
3805m=audio - TDM -
3806}}}},C=34227565{AV=r01/03/01/55/13{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3807v=0
3808c=TN RFC2543 -
3809m=audio - TDM -
3810}}}},C=34227602{AV=r01/03/01/55/21{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3811v=0
3812c=TN RFC2543 -
3813m=audio - TDM -
3814}}}},C=34227616{AV=r01/03/01/55/1{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3815v=0
3816c=TN RFC2543 -
3817m=audio - TDM -
3818}}}},C=34227704{AV=r01/03/01/55/19{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3819v=0
3820c=TN RFC2543 -
3821m=audio - TDM -
3822}}}},C=34227705{AV=r01/03/01/55/18{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3823v=0
3824c=TN RFC2543 -
3825m=audio - TDM -
3826}}}},C=34227715{AV=r01/03/01/55/20{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3827v=0
3828c=TN RFC2543 -
3829m=audio - TDM -
3830}}}},C=34322656{AV=r01/03/01/55/30{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3831v=0
3832c=TN RFC2543 -
3833m=audio - TDM -
3834}}}},C=34322804{AV=r01/03/01/55/24{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3835v=0
3836c=TN RFC2543 -
3837m=audio - TDM -
3838}}}},C=34322812{AV=r01/03/01/55/15{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3839v=0
3840c=TN RFC2543 -
3841m=audio - TDM -
3842}}}},C=34322825{AV=r01/03/01/55/4{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3843v=0
3844c=TN RFC2543 -
3845m=audio - TDM -
3846}}}},C=34322836{AV=r01/03/01/55/17{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3847v=0
3848c=TN RFC2543 -
3849m=audio - TDM -
3850}}}},C=34323007{AV=r01/03/01/55/6{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3851v=0
3852c=TN RFC2543 -
3853m=audio - TDM -
3854}}}},C=34323008{AV=r01/03/01/55/2{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3855v=0
3856c=TN RFC2543 -
3857m=audio - TDM -
3858}}}},C=34323071{AV=r01/03/01/55/28{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3859v=0
3860c=TN RFC2543 -
3861m=audio - TDM -
3862}}}},C=34323075{AV=r01/03/01/55/29{M{TS{eri_terminfo/dev_state=norm,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=IV},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x00},L{
3863v=0
3864c=TN RFC2543 -
3865m=audio - TDM -
3866}}}}}">>.
3867
3868
3869%% size36_27_11_bad.txt
3870flex_compact_otp10998_msg02() ->
3871    <<"!/2 stofmg0
3872P=25167656{C=34205358{AV=r01/03/01/27/22{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3873v=0
3874c=TN RFC2543 -
3875m=audio - TDM -
3876}}}},C=34205359{AV=r01/03/01/27/13{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3877v=0
3878c=TN RFC2543 -
3879m=audio - TDM -
3880}}}},C=34205360{AV=r01/03/01/27/23{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3881v=0
3882c=TN RFC2543 -
3883m=audio - TDM -
3884}}}},C=34227786{AV=r01/03/01/27/8{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3885v=0
3886c=TN RFC2543 -
3887m=audio - TDM -
3888}}}},C=34230890{AV=r01/03/01/27/15{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3889v=0
3890c=TN RFC2543 -
3891m=audio - TDM -
3892}}}},C=34230903{AV=r01/03/01/27/24{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3893v=0
3894c=TN RFC2543 -
3895m=audio - TDM -
3896}}}},C=34230904{AV=r01/03/01/27/14{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3897v=0
3898c=TN RFC2543 -
3899m=audio - TDM -
3900}}}},C=34230905{AV=r01/03/01/27/12{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3901v=0
3902c=TN RFC2543 -
3903m=audio - TDM -
3904}}}},C=34230913{AV=r01/03/01/27/4{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3905v=0
3906c=TN RFC2543 -
3907m=audio - TDM -
3908}}}},C=34316801{AV=r01/03/01/27/9{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3909v=0
3910c=TN RFC2543 -
3911m=audio - TDM -
3912}}}},C=34316805{AV=r01/03/01/27/19{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3913v=0
3914c=TN RFC2543 -
3915m=audio - TDM -
3916}}}},C=34316814{AV=r01/03/01/27/5{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3917v=0
3918c=TN RFC2543 -
3919m=audio - TDM -
3920}}}},C=34316829{AV=r01/03/01/27/7{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3921v=0
3922c=TN RFC2543 -
3923m=audio - TDM -
3924}}}},C=34323013{AV=r01/03/01/27/6{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3925v=0
3926c=TN RFC2543 -
3927m=audio - TDM -
3928}}}},C=34107499{AV=r01/03/01/11/14{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3929v=0
3930c=TN RFC2543 -
3931m=audio - TDM -
3932}}}},C=34107500{AV=r01/03/01/11/4{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3933v=0
3934c=TN RFC2543 -
3935m=audio - TDM -
3936}}}},C=34107505{AV=r01/03/01/11/8{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3937v=0
3938c=TN RFC2543 -
3939m=audio - TDM -
3940}}}},C=34316766{AV=r01/03/01/11/3{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3941v=0
3942c=TN RFC2543 -
3943m=audio - TDM -
3944}}}},C=34316768{AV=r01/03/01/11/10{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3945v=0
3946c=TN RFC2543 -
3947m=audio - TDM -
3948}}}},C=34316786{AV=r01/03/01/11/12{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3949v=0
3950c=TN RFC2543 -
3951m=audio - TDM -
3952}}}},C=34316787{AV=r01/03/01/11/1{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3953v=0
3954c=TN RFC2543 -
3955m=audio - TDM -
3956}}}},C=34316793{AV=r01/03/01/11/22{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3957v=0
3958c=TN RFC2543 -
3959m=audio - TDM -
3960}}}},C=34316794{AV=r01/03/01/11/24{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3961v=0
3962c=TN RFC2543 -
3963m=audio - TDM -
3964}}}},C=34316795{AV=r01/03/01/11/31{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3965v=0
3966c=TN RFC2543 -
3967m=audio - TDM -
3968}}}},C=34316797{AV=r01/03/01/11/18{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3969v=0
3970c=TN RFC2543 -
3971m=audio - TDM -
3972}}}},C=34316804{AV=r01/03/01/11/15{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3973v=0
3974c=TN RFC2543 -
3975m=audio - TDM -
3976}}}},C=34316807{AV=r01/03/01/11/6{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3977v=0
3978c=TN RFC2543 -
3979m=audio - TDM -
3980}}}},C=34316815{AV=r01/03/01/11/16{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3981v=0
3982c=TN RFC2543 -
3983m=audio - TDM -
3984}}}},C=34316819{AV=r01/03/01/11/28{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3985v=0
3986c=TN RFC2543 -
3987m=audio - TDM -
3988}}}},C=34316824{AV=r01/03/01/11/17{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3989v=0
3990c=TN RFC2543 -
3991m=audio - TDM -
3992}}}},C=34316826{AV=r01/03/01/11/25{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3993v=0
3994c=TN RFC2543 -
3995m=audio - TDM -
3996}}}},C=34316827{AV=r01/03/01/11/9{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
3997v=0
3998c=TN RFC2543 -
3999m=audio - TDM -
4000}}}},C=34316828{AV=r01/03/01/11/21{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4001v=0
4002c=TN RFC2543 -
4003m=audio - TDM -
4004}}}},C=34316830{AV=r01/03/01/11/2{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4005v=0
4006c=TN RFC2543 -
4007m=audio - TDM -
4008}}}},C=34316832{AV=r01/03/01/11/11{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4009v=0
4010c=TN RFC2543 -
4011m=audio - TDM -
4012}}}},C=34316850{AV=r01/03/01/11/5{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4013v=0
4014c=TN RFC2543 -
4015m=audio - TDM -
4016}}}}}">>.
4017
4018
4019%% size41_38_55_good.txt
4020flex_compact_otp10998_msg03() ->
4021    <<"!/2 stofmg0
4022P=25166035{C=34227581{AV=r01/03/01/38/22{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4023v=0
4024c=TN RFC2543 -
4025m=audio - TDM -
4026}}}},C=34227613{AV=r01/03/01/38/12{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4027v=0
4028c=TN RFC2543 -
4029m=audio - TDM -
4030}}}},C=34227744{AV=r01/03/01/38/11{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4031v=0
4032c=TN RFC2543 -
4033m=audio - TDM -
4034}}}},C=34227755{AV=r01/03/01/38/2{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4035v=0
4036c=TN RFC2543 -
4037m=audio - TDM -
4038}}}},C=34227768{AV=r01/03/01/38/14{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4039v=0
4040c=TN RFC2543 -
4041m=audio - TDM -
4042}}}},C=34227774{AV=r01/03/01/38/15{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4043v=0
4044c=TN RFC2543 -
4045m=audio - TDM -
4046}}}},C=34227775{AV=r01/03/01/38/16{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4047v=0
4048c=TN RFC2543 -
4049m=audio - TDM -
4050}}}},C=34323122{AV=r01/03/01/38/7{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4051v=0
4052c=TN RFC2543 -
4053m=audio - TDM -
4054}}}},C=34323156{AV=r01/03/01/38/8{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4055v=0
4056c=TN RFC2543 -
4057m=audio - TDM -
4058}}}},C=34323260{AV=r01/03/01/38/13{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4059v=0
4060c=TN RFC2543 -
4061m=audio - TDM -
4062}}}},C=34323272{AV=r01/03/01/38/30{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4063v=0
4064c=TN RFC2543 -
4065m=audio - TDM -
4066}}}},C=34323273{AV=r01/03/01/38/29{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4067v=0
4068c=TN RFC2543 -
4069m=audio - TDM -
4070}}}},C=34323275{AV=r01/03/01/38/25{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4071v=0
4072c=TN RFC2543 -
4073m=audio - TDM -
4074}}}},C=34323276{AV=r01/03/01/38/28{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4075v=0
4076c=TN RFC2543 -
4077m=audio - TDM -
4078}}}},C=34323279{AV=r01/03/01/38/26{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4079v=0
4080c=TN RFC2543 -
4081m=audio - TDM -
4082}}}},C=34323280{AV=r01/03/01/38/24{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4083v=0
4084c=TN RFC2543 -
4085m=audio - TDM -
4086}}}},C=34323281{AV=r01/03/01/38/27{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4087v=0
4088c=TN RFC2543 -
4089m=audio - TDM -
4090}}}},C=34323284{AV=r01/03/01/38/23{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4091v=0
4092c=TN RFC2543 -
4093m=audio - TDM -
4094}}}},C=34129764{AV=r01/03/01/55/31{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4095v=0
4096c=TN RFC2543 -
4097m=audio - TDM -
4098}}}},C=34227463{AV=r01/03/01/55/26{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4099v=0
4100c=TN RFC2543 -
4101m=audio - TDM -
4102}}}},C=34227472{AV=r01/03/01/55/22{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4103v=0
4104c=TN RFC2543 -
4105m=audio - TDM -
4106}}}},C=34227484{AV=r01/03/01/55/16{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4107v=0
4108c=TN RFC2543 -
4109m=audio - TDM -
4110}}}},C=34227555{AV=r01/03/01/55/5{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4111v=0
4112c=TN RFC2543 -
4113m=audio - TDM -
4114}}}},C=34227556{AV=r01/03/01/55/14{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4115v=0
4116c=TN RFC2543 -
4117m=audio - TDM -
4118}}}},C=34227557{AV=r01/03/01/55/10{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4119v=0
4120c=TN RFC2543 -
4121m=audio - TDM -
4122}}}},C=34227563{AV=r01/03/01/55/7{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4123v=0
4124c=TN RFC2543 -
4125m=audio - TDM -
4126}}}},C=34227565{AV=r01/03/01/55/13{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4127v=0
4128c=TN RFC2543 -
4129m=audio - TDM -
4130}}}},C=34227602{AV=r01/03/01/55/21{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4131v=0
4132c=TN RFC2543 -
4133m=audio - TDM -
4134}}}},C=34227616{AV=r01/03/01/55/1{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4135v=0
4136c=TN RFC2543 -
4137m=audio - TDM -
4138}}}},C=34227704{AV=r01/03/01/55/19{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4139v=0
4140c=TN RFC2543 -
4141m=audio - TDM -
4142}}}},C=34227705{AV=r01/03/01/55/18{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4143v=0
4144c=TN RFC2543 -
4145m=audio - TDM -
4146}}}},C=34227715{AV=r01/03/01/55/20{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4147v=0
4148c=TN RFC2543 -
4149m=audio - TDM -
4150}}}},C=34322656{AV=r01/03/01/55/30{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4151v=0
4152c=TN RFC2543 -
4153m=audio - TDM -
4154}}}},C=34322804{AV=r01/03/01/55/24{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4155v=0
4156c=TN RFC2543 -
4157m=audio - TDM -
4158}}}},C=34322812{AV=r01/03/01/55/15{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4159v=0
4160c=TN RFC2543 -
4161m=audio - TDM -
4162}}}},C=34322825{AV=r01/03/01/55/4{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4163v=0
4164c=TN RFC2543 -
4165m=audio - TDM -
4166}}}},C=34322836{AV=r01/03/01/55/17{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4167v=0
4168c=TN RFC2543 -
4169m=audio - TDM -
4170}}}},C=34323007{AV=r01/03/01/55/6{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4171v=0
4172c=TN RFC2543 -
4173m=audio - TDM -
4174}}}},C=34323008{AV=r01/03/01/55/2{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4175v=0
4176c=TN RFC2543 -
4177m=audio - TDM -
4178}}}},C=34323071{AV=r01/03/01/55/28{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4179v=0
4180c=TN RFC2543 -
4181m=audio - TDM -
4182}}}},C=34323075{AV=r01/03/01/55/29{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4183v=0
4184c=TN RFC2543 -
4185m=audio - TDM -
4186}}}}}">>.
4187
4188
4189%% size42_38_55_bad.txt
4190flex_compact_otp10998_msg04() ->
4191    <<"!/2 stofmg0
4192P=33555020{C=34227581{AV=r01/03/01/38/22{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4193v=0
4194c=TN RFC2543 -
4195m=audio - TDM -
4196}}}},C=34227613{AV=r01/03/01/38/12{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4197v=0
4198c=TN RFC2543 -
4199m=audio - TDM -
4200}}}},C=34227744{AV=r01/03/01/38/11{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4201v=0
4202c=TN RFC2543 -
4203m=audio - TDM -
4204}}}},C=34227755{AV=r01/03/01/38/2{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4205v=0
4206c=TN RFC2543 -
4207m=audio - TDM -
4208}}}},C=34227768{AV=r01/03/01/38/14{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4209v=0
4210c=TN RFC2543 -
4211m=audio - TDM -
4212}}}},C=34227774{AV=r01/03/01/38/15{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4213v=0
4214c=TN RFC2543 -
4215m=audio - TDM -
4216}}}},C=34227775{AV=r01/03/01/38/16{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4217v=0
4218c=TN RFC2543 -
4219m=audio - TDM -
4220}}}},C=34323119{AV=r01/03/01/38/9{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4221v=0
4222c=TN RFC2543 -
4223m=audio - TDM -
4224}}}},C=34323122{AV=r01/03/01/38/7{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4225v=0
4226c=TN RFC2543 -
4227m=audio - TDM -
4228}}}},C=34323156{AV=r01/03/01/38/8{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4229v=0
4230c=TN RFC2543 -
4231m=audio - TDM -
4232}}}},C=34323260{AV=r01/03/01/38/13{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4233v=0
4234c=TN RFC2543 -
4235m=audio - TDM -
4236}}}},C=34323272{AV=r01/03/01/38/30{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4237v=0
4238c=TN RFC2543 -
4239m=audio - TDM -
4240}}}},C=34323273{AV=r01/03/01/38/29{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4241v=0
4242c=TN RFC2543 -
4243m=audio - TDM -
4244}}}},C=34323275{AV=r01/03/01/38/25{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4245v=0
4246c=TN RFC2543 -
4247m=audio - TDM -
4248}}}},C=34323276{AV=r01/03/01/38/28{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4249v=0
4250c=TN RFC2543 -
4251m=audio - TDM -
4252}}}},C=34323279{AV=r01/03/01/38/26{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4253v=0
4254c=TN RFC2543 -
4255m=audio - TDM -
4256}}}},C=34323280{AV=r01/03/01/38/24{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4257v=0
4258c=TN RFC2543 -
4259m=audio - TDM -
4260}}}},C=34323281{AV=r01/03/01/38/27{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4261v=0
4262c=TN RFC2543 -
4263m=audio - TDM -
4264}}}},C=34323284{AV=r01/03/01/38/23{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4265v=0
4266c=TN RFC2543 -
4267m=audio - TDM -
4268}}}},C=34129764{AV=r01/03/01/55/31{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4269v=0
4270c=TN RFC2543 -
4271m=audio - TDM -
4272}}}},C=34227463{AV=r01/03/01/55/26{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4273v=0
4274c=TN RFC2543 -
4275m=audio - TDM -
4276}}}},C=34227472{AV=r01/03/01/55/22{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4277v=0
4278c=TN RFC2543 -
4279m=audio - TDM -
4280}}}},C=34227484{AV=r01/03/01/55/16{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4281v=0
4282c=TN RFC2543 -
4283m=audio - TDM -
4284}}}},C=34227555{AV=r01/03/01/55/5{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4285v=0
4286c=TN RFC2543 -
4287m=audio - TDM -
4288}}}},C=34227556{AV=r01/03/01/55/14{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4289v=0
4290c=TN RFC2543 -
4291m=audio - TDM -
4292}}}},C=34227557{AV=r01/03/01/55/10{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4293v=0
4294c=TN RFC2543 -
4295m=audio - TDM -
4296}}}},C=34227563{AV=r01/03/01/55/7{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4297v=0
4298c=TN RFC2543 -
4299m=audio - TDM -
4300}}}},C=34227565{AV=r01/03/01/55/13{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4301v=0
4302c=TN RFC2543 -
4303m=audio - TDM -
4304}}}},C=34227602{AV=r01/03/01/55/21{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4305v=0
4306c=TN RFC2543 -
4307m=audio - TDM -
4308}}}},C=34227616{AV=r01/03/01/55/1{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4309v=0
4310c=TN RFC2543 -
4311m=audio - TDM -
4312}}}},C=34227704{AV=r01/03/01/55/19{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4313v=0
4314c=TN RFC2543 -
4315m=audio - TDM -
4316}}}},C=34227705{AV=r01/03/01/55/18{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4317v=0
4318c=TN RFC2543 -
4319m=audio - TDM -
4320}}}},C=34227715{AV=r01/03/01/55/20{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4321v=0
4322c=TN RFC2543 -
4323m=audio - TDM -
4324}}}},C=34322656{AV=r01/03/01/55/30{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4325v=0
4326c=TN RFC2543 -
4327m=audio - TDM -
4328}}}},C=34322804{AV=r01/03/01/55/24{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4329v=0
4330c=TN RFC2543 -
4331m=audio - TDM -
4332}}}},C=34322812{AV=r01/03/01/55/15{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4333v=0
4334c=TN RFC2543 -
4335m=audio - TDM -
4336}}}},C=34322825{AV=r01/03/01/55/4{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4337v=0
4338c=TN RFC2543 -
4339m=audio - TDM -
4340}}}},C=34322836{AV=r01/03/01/55/17{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4341v=0
4342c=TN RFC2543 -
4343m=audio - TDM -
4344}}}},C=34323007{AV=r01/03/01/55/6{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4345v=0
4346c=TN RFC2543 -
4347m=audio - TDM -
4348}}}},C=34323008{AV=r01/03/01/55/2{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4349v=0
4350c=TN RFC2543 -
4351m=audio - TDM -
4352}}}},C=34323071{AV=r01/03/01/55/28{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4353v=0
4354c=TN RFC2543 -
4355m=audio - TDM -
4356}}}},C=34323075{AV=r01/03/01/55/29{M{TS{eri_terminfo/dev_state=link,eri_terminfo/dev_type=cee1,eri_terminfo/law_conv=on,SI=OS},O{MO=SR,RV=OFF,semper/act=on,tdmc/ec=off,semper/termstatus=0x01},L{
4357v=0
4358c=TN RFC2543 -
4359m=audio - TDM -
4360}}}}}">>.
4361
4362
4363flex_compact_otp10998_num() ->
4364    10.
4365
4366flex_compact_otp10998_msg01(suite) ->
4367    [];
4368flex_compact_otp10998_msg01(Config) when is_list(Config) ->
4369    %% put(dbg, true),
4370    %% put(severity, trc),
4371    d("flex_compact_otp10998_msg01 -> entry", []),
4372    Msg  = flex_compact_otp10998_msg01(),
4373    d("flex_compact_otp10998_msg01 -> message created", []),
4374    Conf =
4375	try flex_scanner_conf(Config) of
4376	    C ->
4377		C
4378	catch
4379	    exit:Error ->
4380		e("Failed getting flex config: "
4381		  "~n   Error: ~p", [Error]),
4382		exit(Error)
4383	end,
4384    d("flex_compact_otp10998_msg01 -> flex config generated", []),
4385    flex_compact_otp10998([Conf], flex_compact_otp10998_num(), Msg).
4386
4387flex_compact_otp10998_msg02(suite) ->
4388    [];
4389flex_compact_otp10998_msg02(Config) when is_list(Config) ->
4390    %% put(dbg, true),
4391    %% put(severity, trc),
4392    d("flex_compact_otp10998_msg02 -> entry", []),
4393    Msg  = flex_compact_otp10998_msg02(),
4394    d("flex_compact_otp10998_msg02 -> message created", []),
4395    Conf =
4396	try flex_scanner_conf(Config) of
4397	    C ->
4398		C
4399	catch
4400	    exit:Error ->
4401		e("Failed getting flex config: "
4402		  "~n   Error: ~p", [Error]),
4403		exit(Error)
4404	end,
4405    d("flex_compact_otp10998_msg02 -> flex config generated", []),
4406    flex_compact_otp10998([Conf], flex_compact_otp10998_num(), Msg).
4407
4408flex_compact_otp10998_msg03(suite) ->
4409    [];
4410flex_compact_otp10998_msg03(Config) when is_list(Config) ->
4411    %% put(dbg, true),
4412    %% put(severity, trc),
4413    d("flex_compact_otp10998_msg03 -> entry", []),
4414    Msg  = flex_compact_otp10998_msg03(),
4415    d("flex_compact_otp10998_msg03 -> message created", []),
4416    Conf =
4417	try flex_scanner_conf(Config) of
4418	    C ->
4419		C
4420	catch
4421	    exit:Error ->
4422		e("Failed getting flex config: "
4423		  "~n   Error: ~p", [Error]),
4424		exit(Error)
4425	end,
4426    d("flex_compact_otp10998_msg03 -> flex config generated", []),
4427    flex_compact_otp10998([Conf], flex_compact_otp10998_num(), Msg).
4428
4429flex_compact_otp10998_msg04(suite) ->
4430    [];
4431flex_compact_otp10998_msg04(Config) when is_list(Config) ->
4432    %% put(dbg, true),
4433    %% put(severity, trc),
4434    d("flex_compact_otp10998_msg04 -> entry", []),
4435    Msg  = flex_compact_otp10998_msg04(),
4436    d("flex_compact_otp10998_msg04 -> message created", []),
4437    Conf =
4438	try flex_scanner_conf(Config) of
4439	    C ->
4440		C
4441	catch
4442	    exit:Error ->
4443		e("Failed getting flex config: "
4444		  "~n   Error: ~p", [Error]),
4445		exit(Error)
4446	end,
4447    d("flex_compact_otp10998_msg04 -> flex config generated", []),
4448    flex_compact_otp10998([Conf], flex_compact_otp10998_num(), Msg).
4449
4450flex_compact_otp10998(EC, N, BinMsg) ->
4451    Codec  = megaco_compact_text_encoder,
4452    Decode = fun(No) ->
4453		     case decode_message(Codec, false, EC, BinMsg) of
4454			 {ok, _Msg} ->
4455			     d("flex_compact_otp10998 -> decode ok", []),
4456			     ok;
4457			 {error, Reason} ->
4458			     e("flex_compact_otp10998 -> "
4459			       "decode ~w failed: ~p", [No, Reason]),
4460			     throw({error, No, Reason})
4461		     end
4462	     end,
4463    do_flex_compact_otp10998(N, Decode).
4464
4465do_flex_compact_otp10998(N, Decode) when N > 0 ->
4466    Decode(N),
4467    do_flex_compact_otp10998(N-1, Decode);
4468do_flex_compact_otp10998(_, _) ->
4469    ok.
4470
4471
4472
4473%% ==============================================================
4474%%
4475%% P r e t t y   T e s t c a s e s
4476%%
4477
4478pretty_otp4632_msg1(suite) ->
4479    [];
4480pretty_otp4632_msg1(Config) when is_list(Config) ->
4481    d("pretty_otp4632_msg1 -> entry", []),
4482    ?ACQUIRE_NODES(1, Config),
4483    Msg0 = pretty_otp4632_msg1(),
4484    case encode_message(megaco_pretty_text_encoder, [], Msg0) of
4485	{ok, BinMsg} when is_binary(BinMsg) ->
4486	    {ok, Msg1} = decode_message(megaco_pretty_text_encoder, false,
4487					[], BinMsg),
4488	    ok = chk_MegacoMessage(Msg0, Msg1);
4489	Else ->
4490	    t("pretty_otp4632_msg1 -> "
4491	      "~n   Else: ~w", [Else]),
4492	    exit({unexpected_decode_result, Else})
4493    end.
4494
4495pretty_otp4632_msg1() ->
4496    msg4(?MG1_MID_NO_PORT, "901 mg col boot").
4497
4498pretty_otp4632_msg2(suite) ->
4499    [];
4500pretty_otp4632_msg2(Config) when is_list(Config) ->
4501    d("pretty_otp4632_msg2 -> entry", []),
4502    ?ACQUIRE_NODES(1, Config),
4503    Msg0 = pretty_otp4632_msg2(),
4504    case encode_message(megaco_pretty_text_encoder, [], Msg0) of
4505	{ok, BinMsg} when is_binary(BinMsg) ->
4506	    {ok, Msg1} = decode_message(megaco_pretty_text_encoder, false,
4507					[], BinMsg),
4508	    ok = chk_MegacoMessage(Msg0,Msg1);
4509	Else ->
4510	    t("pretty_otp4632_msg2 -> "
4511	      "~n   Else: ~w", [Else]),
4512	    exit({unexpected_decode_result, Else})
4513    end.
4514
4515pretty_otp4632_msg2() ->
4516    msg4(?MG1_MID_NO_PORT, "901").
4517
4518
4519pretty_otp4632_msg3(suite) ->
4520    [];
4521pretty_otp4632_msg3(Config) when is_list(Config) ->
4522    d("pretty_otp4632_msg3 -> entry", []),
4523    ?ACQUIRE_NODES(1, Config),
4524    Msg0 = pretty_otp4632_msg3(),
4525    Bin0 = list_to_binary(Msg0),
4526    case decode_message(megaco_pretty_text_encoder,
4527			false, [], Bin0) of
4528	{ok, Msg} when is_record(Msg, 'MegacoMessage') ->
4529	    {ok, Bin1} = encode_message(megaco_pretty_text_encoder, [], Msg),
4530	    Msg1 = binary_to_list(Bin1),
4531	    %% io:format("Msg1:~n~s~n", [Msg1]),
4532	    Msg0 = Msg1,
4533	    ok;
4534	Else ->
4535	    t("pretty_otp4632_msg3 -> "
4536	      "~n   Else: ~w", [Else]),
4537	    exit({unexpected_decode_result, Else})
4538    end.
4539
4540pretty_otp4632_msg3() ->
4541    M = "MEGACO/" ?VERSION_STR " [124.124.124.222]\nTransaction = 9998 {\n\tContext = - {\n\t\tServiceChange = root {\n\t\t\tServices {\n\t\t\t\tMethod = Restart,\n\t\t\t\tServiceChangeAddress = 55555,\n\t\t\t\tProfile = resgw/1,\n\t\t\t\tReason = \"901\"\n\t\t\t}\n\t\t}\n\t}\n}",
4542    M.
4543
4544
4545pretty_otp4632_msg4(suite) ->
4546    [];
4547pretty_otp4632_msg4(Config) when is_list(Config) ->
4548    d("pretty_otp4632_msg4 -> entry", []),
4549    ?ACQUIRE_NODES(1, Config),
4550    Msg0 = pretty_otp4632_msg4(),
4551    Bin0 = list_to_binary(Msg0),
4552    case decode_message(megaco_pretty_text_encoder, false, [], Bin0) of
4553	{ok, Msg} when is_record(Msg, 'MegacoMessage') ->
4554	    {ok, Bin1} = encode_message(megaco_pretty_text_encoder, [], Msg),
4555	    Msg1 = binary_to_list(Bin1),
4556	    %% io:format("Msg1:~n~s~n", [Msg1]),
4557	    pretty_otp4632_msg4_chk(Msg0,Msg1);
4558	Else ->
4559	    t("pretty_otp4632_msg4 -> "
4560	      "~n   Else: ~w", [Else]),
4561	    exit({unexpected_decode_result, Else})
4562    end.
4563
4564
4565pretty_otp4632_msg4() ->
4566    M = "MEGACO/" ?VERSION_STR " [124.124.124.222]\nTransaction = 9998 {\n\tContext = - {\n\t\tServiceChange = root {\n\t\t\tServices {\n\t\t\t\tMethod = Restart,\n\t\t\t\tServiceChangeAddress = 55555,\n\t\t\t\tProfile = resgw/1,\n\t\t\t\tReason = 901\n\t\t\t}\n\t\t}\n\t}\n}",
4567    M.
4568
4569
4570pretty_otp4632_msg4_chk([], []) ->
4571    exit(messages_not_eq);
4572pretty_otp4632_msg4_chk([], Rest1) ->
4573    exit({messages_not_eq1, Rest1});
4574pretty_otp4632_msg4_chk(Rest0, []) ->
4575    exit({messages_not_eq0, Rest0});
4576pretty_otp4632_msg4_chk([$R,$e,$a,$s,$o,$n,$ ,$=,$ ,$9,$0,$1|_Rest0],
4577			[$R,$e,$a,$s,$o,$n,$ ,$=,$ ,$",$9,$0,$1,$"|_Rest1]) ->
4578    ok;
4579pretty_otp4632_msg4_chk([_|Rest0], [_|Rest1]) ->
4580    pretty_otp4632_msg4_chk(Rest0,Rest1).
4581
4582
4583pretty_otp4710_msg1(suite) ->
4584    [];
4585pretty_otp4710_msg1(Config) when is_list(Config) ->
4586    d("pretty_otp4710_msg1 -> entry", []),
4587    ?ACQUIRE_NODES(1, Config),
4588    Msg0 = pretty_otp4710_msg1(),
4589    case encode_message(megaco_pretty_text_encoder, [], Msg0) of
4590	{ok, Bin} when is_binary(Bin) ->
4591	    {ok, Msg1} = decode_message(megaco_pretty_text_encoder, false,
4592					[], Bin),
4593	    ok = chk_MegacoMessage(Msg0,Msg1);
4594	Else ->
4595	    t("pretty_otp4710_msg1 -> "
4596	      "~n   Else: ~w", [Else]),
4597	    exit({unexpected_decode_result, Else})
4598    end.
4599
4600pretty_otp4710_msg1() ->
4601    msg40().
4602
4603
4604pretty_otp4710_msg2(suite) ->
4605    [];
4606pretty_otp4710_msg2(Config) when is_list(Config) ->
4607    d("pretty_otp4710_msg2 -> entry", []),
4608    ?ACQUIRE_NODES(1, Config),
4609    Msg0 = pretty_otp4710_msg2(),
4610    Bin0 = list_to_binary(Msg0),
4611    case decode_message(megaco_pretty_text_encoder, false, [], Bin0) of
4612	{ok, Msg} when is_record(Msg, 'MegacoMessage') ->
4613	    {ok, Bin1} = encode_message(megaco_pretty_text_encoder, [], Msg),
4614	    Msg1 = binary_to_list(Bin1),
4615	    %% io:format("Msg1:~n~s~n", [Msg1]),
4616	    pretty_otp4710_msg2_chk(Msg0,Msg1);
4617	Else ->
4618	    t("pretty_otp4710_msg2 -> "
4619	      "~n   Else: ~w", [Else]),
4620	    exit({unexpected_decode_result, Else})
4621    end.
4622
4623pretty_otp4710_msg2() ->
4624    "Authentication = 0xEFCDAB89:0x12345678:0x1234567889ABCDEF76543210\nMEGACO/" ?VERSION_STR " [124.124.124.222]\nTransaction = 9998 {\n\tContext = - {\n\t\tServiceChange = root {\n\t\t\tServices {\n\t\t\t\tMethod = Restart,\n\t\t\t\tServiceChangeAddress = 55555,\n\t\t\t\tProfile = resgw/1,\n\t\t\t\tReason = \"901 mg col boot\"\n\t\t\t}\n\t\t}\n\t}\n}".
4625
4626pretty_otp4710_msg2_chk(Msg,Msg) ->
4627    ok;
4628pretty_otp4710_msg2_chk(
4629  [$A,$u,$t,$h,$e,$n,$t,$i,$c,$a,$t,$i,$o,$n,$=,$ |Msg0],
4630  [$A,$u,$t,$h,$e,$n,$t,$i,$c,$a,$t,$i,$o,$n,$=,$ |Msg1]) ->
4631    {AH0, Rest0} = pretty_otp4710_msg2_chk_ah(Msg0, []),
4632    {AH1, Rest1} = pretty_otp4710_msg2_chk_ah(Msg1, []),
4633    case AH0 == AH1 of
4634	true ->
4635	    exit({message_not_equal, Rest0, Rest1});
4636	false ->
4637	    exit({auth_header_not_equal, AH0, AH1})
4638    end.
4639
4640pretty_otp4710_msg2_chk_ah([], _Acc) ->
4641    exit(no_auth_header_found);
4642pretty_otp4710_msg2_chk_ah([$M,$E,$G,$A,$C,$O,$/,_|Rest], Acc) ->
4643    {lists:reverse(Acc), Rest};
4644pretty_otp4710_msg2_chk_ah([C|R], Acc) ->
4645    pretty_otp4710_msg2_chk_ah(R, [C|Acc]).
4646
4647
4648pretty_otp4945_msg1(suite) ->
4649    [];
4650pretty_otp4945_msg1(Config) when is_list(Config) ->
4651    d("pretty_otp4945_msg1 -> entry", []),
4652    ?ACQUIRE_NODES(1, Config),
4653    Msg0 = pretty_otp4945_msg1(),
4654    Bin0 = list_to_binary(Msg0),
4655    case decode_message(megaco_pretty_text_encoder, false, [], Bin0) of
4656	{error, [{reason, Reason}|_]} ->
4657	    case Reason of
4658		{missing_required_serviceChangeParm, [serviceChangeReason]} ->
4659		    ok;
4660		Else ->
4661		    t("pretty_otp4945_msg1 -> "
4662		      "~n   Else: ~w", [Else]),
4663		    exit({unexpected_decode_result, Else})
4664	    end;
4665	Else ->
4666	    io:format("pretty_otp4945_msg1 -> "
4667		      "~n   Else: ~w"
4668		      "~n", [Else]),
4669	    exit({unexpected_decode_result, Else})
4670    end.
4671
4672pretty_otp4945_msg1() ->
4673"MEGACO/" ?VERSION_STR " [124.124.124.222] Transaction = 9998 {
4674   Context = - {
4675      ServiceChange = ROOT {
4676         Services {
4677            Method = Restart,
4678            ServiceChangeAddress = 55555,
4679            Profile = ResGW/1
4680         }
4681      }
4682   }
4683}".
4684
4685
4686pretty_otp4945_msg2(suite) ->
4687    [];
4688pretty_otp4945_msg2(Config) when is_list(Config) ->
4689    d("pretty_otp4945_msg2 -> entry", []),
4690    ?ACQUIRE_NODES(1, Config),
4691    Msg0 = pretty_otp4945_msg2(),
4692    Bin0 = list_to_binary(Msg0),
4693    case decode_message(megaco_pretty_text_encoder, false, [], Bin0) of
4694	{error, [{reason, Reason}|_]} ->
4695	    case Reason of
4696		{missing_required_serviceChangeParm, [serviceChangeMethod]} ->
4697		    ok;
4698		Else ->
4699		    t("pretty_otp4945_msg2 -> "
4700		      "~n   Else: ~w", [Else]),
4701		    exit({unexpected_decode_result, Else})
4702	    end;
4703	Else ->
4704	    t("pretty_otp4945_msg2 -> "
4705	      "~n   Else: ~w", [Else]),
4706	    exit({unexpected_decode_result, Else})
4707    end.
4708
4709pretty_otp4945_msg2() ->
4710"MEGACO/" ?VERSION_STR " [124.124.124.222] Transaction = 9998 {
4711   Context = - {
4712      ServiceChange = ROOT {
4713         Services {
4714            Reason = 901,
4715            ServiceChangeAddress = 55555,
4716            Profile = ResGW/1
4717         }
4718      }
4719   }
4720}".
4721
4722
4723pretty_otp4945_msg3(suite) ->
4724    [];
4725pretty_otp4945_msg3(Config) when is_list(Config) ->
4726    d("pretty_otp4945_msg3 -> entry", []),
4727    ?ACQUIRE_NODES(1, Config),
4728    Msg0 = pretty_otp4945_msg3(),
4729    Bin0 = list_to_binary(Msg0),
4730    case decode_message(megaco_pretty_text_encoder, false, [], Bin0) of
4731	{error, [{reason, Reason}|_]} ->
4732	    case Reason of
4733		{missing_required_serviceChangeParm, [serviceChangeReason, serviceChangeMethod]} ->
4734		    ok;
4735		{missing_required_serviceChangeParm, [serviceChangeMethod, serviceChangeReason]} ->
4736		    ok;
4737		Else ->
4738		    t("pretty_otp4945_msg3 -> "
4739		      "~n   Else: ~w", [Else]),
4740		    exit({unexpected_decode_result, Else})
4741	    end;
4742	Else ->
4743	    t("pretty_otp4945_msg3 -> "
4744	      "~n   Else: ~w", [Else]),
4745	    exit({unexpected_decode_result, Else})
4746    end.
4747
4748pretty_otp4945_msg3() ->
4749"MEGACO/" ?VERSION_STR " [124.124.124.222] Transaction = 9998 {
4750   Context = - {
4751      ServiceChange = ROOT {
4752         Services {
4753            ServiceChangeAddress = 55555,
4754            Profile = ResGW/1
4755         }
4756      }
4757   }
4758}".
4759
4760
4761pretty_otp4945_msg4(suite) ->
4762    [];
4763pretty_otp4945_msg4(Config) when is_list(Config) ->
4764    d("pretty_otp4945_msg4 -> entry", []),
4765    ?ACQUIRE_NODES(1, Config),
4766    Msg0 = pretty_otp4945_msg4(),
4767    Bin0 = list_to_binary(Msg0),
4768    case decode_message(megaco_pretty_text_encoder, false, [], Bin0) of
4769	{ok, _} ->
4770	    ok;
4771	Else ->
4772	    t("pretty_otp4945_msg4 -> "
4773	      "~n   Else: ~w", [Else]),
4774	    exit({unexpected_decode_result, Else})
4775    end.
4776
4777pretty_otp4945_msg4() ->
4778"MEGACO/" ?VERSION_STR " [124.124.124.222] Transaction = 9998 {
4779   Context = - {
4780      ServiceChange = ROOT {
4781         Services {
4782            Method = Restart,
4783            Reason = 901,
4784            ServiceChangeAddress = 55555,
4785            Profile = ResGW/1
4786         }
4787      }
4788   }
4789}".
4790
4791
4792pretty_otp4945_msg5(suite) ->
4793    [];
4794pretty_otp4945_msg5(Config) when is_list(Config) ->
4795    d("pretty_otp4945_msg5 -> entry", []),
4796    ?ACQUIRE_NODES(1, Config),
4797    Msg0 = pretty_otp4945_msg5(),
4798    Bin0 = list_to_binary(Msg0),
4799    case decode_message(megaco_pretty_text_encoder, false, [], Bin0) of
4800	{error, [{reason, Reason}|_]} ->
4801	    case Reason of
4802		{at_most_once_serviceChangeParm, {profile, _Val1, _Val2}} ->
4803		    ok;
4804		Else ->
4805		    io:format("pretty_otp4945_msg6 -> "
4806			      "~n   Else: ~w"
4807			      "~n", [Else]),
4808		    exit({unexpected_decode_result, Else})
4809	    end;
4810	Else ->
4811	    t("pretty_otp4945_msg5 -> "
4812	      "~n   Else: ~w", [Else]),
4813	    exit({unexpected_decode_result, Else})
4814    end.
4815
4816pretty_otp4945_msg5() ->
4817"MEGACO/" ?VERSION_STR " [124.124.124.222] Transaction = 9998 {
4818   Context = - {
4819      ServiceChange = ROOT {
4820         Services {
4821            Method = Restart,
4822            Reason = 901,
4823            Profile = ResGW/1,
4824            ServiceChangeAddress = 55555,
4825            Profile = ResGW/2
4826         }
4827      }
4828   }
4829}".
4830
4831
4832pretty_otp4945_msg6(suite) ->
4833    [];
4834pretty_otp4945_msg6(Config) when is_list(Config) ->
4835    d("pretty_otp4945_msg6 -> entry", []),
4836    ?ACQUIRE_NODES(1, Config),
4837    Msg0 = pretty_otp4945_msg6(),
4838    Bin0 = list_to_binary(Msg0),
4839    case decode_message(megaco_pretty_text_encoder, false, [], Bin0) of
4840	{error, [{reason, Reason}|_]} ->
4841	    case Reason of
4842		{not_both_address_mgcid_serviceChangeParm, _Val1, _Val2} ->
4843		    ok;
4844		Else ->
4845		    io:format("pretty_otp4945_msg6 -> "
4846			      "~n   Else: ~w"
4847			      "~n", [Else]),
4848		    exit({unexpected_decode_result, Else})
4849	    end;
4850	Else ->
4851	    t("pretty_otp4945_msg6 -> "
4852	      "~n   Else: ~w", [Else]),
4853	    exit({unexpected_decode_result, Else})
4854    end.
4855
4856pretty_otp4945_msg6() ->
4857"MEGACO/" ?VERSION_STR " [124.124.124.222] Transaction = 9998 {
4858   Context = - {
4859      ServiceChange = ROOT {
4860         Services {
4861            Method = Restart,
4862               Reason = 901,
4863               ServiceChangeAddress = 55555,
4864               MgcIdToTry = kalle,
4865               Profile = ResGW/1
4866            }
4867         }
4868   }
4869}".
4870
4871
4872pretty_otp4949_msg1(suite) ->
4873    [];
4874pretty_otp4949_msg1(Config) when is_list(Config) ->
4875    d("pretty_otp4949_msg1 -> entry", []),
4876    ?ACQUIRE_NODES(1, Config),
4877    Msg0 = pretty_otp4949_msg1(),
4878    Bin0 = list_to_binary(Msg0),
4879    case decode_message(megaco_pretty_text_encoder, false, [], Bin0) of
4880	{ok, _} ->
4881	    ok;
4882	Else ->
4883	    t("pretty_otp4949_msg1 -> "
4884	      "~n   Else: ~w", [Else]),
4885	    exit({unexpected_decode_result, Else})
4886    end.
4887
4888pretty_otp4949_msg1() ->
4889"MEGACO/" ?VERSION_STR " [124.124.124.222] Reply = 9998 {
4890   Context = - {
4891      ServiceChange = ROOT {
4892         Services {
4893            ServiceChangeAddress = 55555,
4894            Profile = ResGW/1
4895         }
4896      }
4897   }
4898}".
4899
4900
4901pretty_otp4949_msg2(suite) ->
4902    [];
4903pretty_otp4949_msg2(Config) when is_list(Config) ->
4904    d("pretty_otp4949_msg2 -> entry", []),
4905    ?ACQUIRE_NODES(1, Config),
4906    Msg0 = pretty_otp4949_msg2(),
4907    Bin0 = list_to_binary(Msg0),
4908    case decode_message(megaco_pretty_text_encoder, false, [], Bin0) of
4909	{error, [{reason, Reason}|_]} ->
4910	    case Reason of
4911		{at_most_once_servChgReplyParm, {profile, _Val1, _Val2}} ->
4912		    ok;
4913		Else ->
4914		    io:format("pretty_otp4949_msg2 -> "
4915			      "~n   Else: ~w"
4916			      "~n", [Else]),
4917		    exit({unexpected_decode_result, Else})
4918	    end;
4919	Else ->
4920	    t("pretty_otp4949_msg2 -> "
4921	      "~n   Else: ~w", [Else]),
4922	    exit({unexpected_decode_result, Else})
4923    end.
4924
4925pretty_otp4949_msg2() ->
4926"MEGACO/" ?VERSION_STR " [124.124.124.222] Reply = 9998 {
4927   Context = - {
4928      ServiceChange = ROOT {
4929         Services {
4930            Profile = ResGW/1,
4931            ServiceChangeAddress = 55555,
4932            Profile = ResGW/2
4933         }
4934      }
4935   }
4936}".
4937
4938
4939pretty_otp4949_msg3(suite) ->
4940    [];
4941pretty_otp4949_msg3(Config) when is_list(Config) ->
4942    d("pretty_otp4949_msg3 -> entry", []),
4943    ?ACQUIRE_NODES(1, Config),
4944    Msg0 = pretty_otp4949_msg3(),
4945    Bin0 = list_to_binary(Msg0),
4946    case decode_message(megaco_pretty_text_encoder, false, [], Bin0) of
4947	{error, [{reason, Reason}|_]} ->
4948	    case Reason of
4949		{not_both_address_mgcid_servChgReplyParm, _Val1, _Val2} ->
4950		    ok;
4951		Else ->
4952		    io:format("pretty_otp4949_msg3 -> "
4953			      "~n   Else: ~w"
4954			      "~n", [Else]),
4955		    exit({unexpected_decode_result, Else})
4956	    end;
4957	Else ->
4958	    t("pretty_otp4949_msg3 -> "
4959	      "~n   Else: ~w", [Else]),
4960	    exit({unexpected_decode_result, Else})
4961    end.
4962
4963pretty_otp4949_msg3() ->
4964"MEGACO/" ?VERSION_STR " [124.124.124.222] Reply = 9998 {
4965   Context = - {
4966      ServiceChange = ROOT {
4967         Services {
4968            ServiceChangeAddress = 55555,
4969            MgcIdToTry = kalle,
4970            Profile = ResGW/1
4971         }
4972      }
4973   }
4974}".
4975
4976
4977pretty_otp5042_msg1(suite) ->
4978    [];
4979pretty_otp5042_msg1(Config) when is_list(Config) ->
4980    d("pretty_otp5042_msg1 -> entry", []),
4981    ?ACQUIRE_NODES(1, Config),
4982    Msg0 = pretty_otp5042_msg1(),
4983    Bin0 = list_to_binary(Msg0),
4984    case decode_message(megaco_pretty_text_encoder, false, [], Bin0) of
4985	{error, [{reason, Reason}|_]} ->
4986	    case Reason of
4987		{_, _Mod, {bad_timeStamp, TimeStamp}} ->
4988		    exit({bad_timeStamp, TimeStamp});
4989		_ ->
4990		    io:format("pretty_otp5042_msg1 -> "
4991			      "~n   Reason: ~w"
4992			      "~n", [Reason]),
4993		    exit({unexpected_decode_result, Reason})
4994	    end;
4995	{ok, M} ->
4996	    t("pretty_otp5042_msg1 -> successfull decode:"
4997	      "~n~p", [M]),
4998	    ok
4999    end.
5000
5001pretty_otp5042_msg1() ->
5002"MEGACO/" ?VERSION_STR " <CATAPULT>:2944
5003Transaction = 102 {
5004Context =  5 { Notify =  MUX/1 { ObservedEvents = 1 {
5005h245bh/h245msgin { Stream =  1
5006, h245enc =
50070270020600088175000653401004100403E802E00180018001780680000034301160000700088175010101007A0100020001800001320000C0000219D005027F0070500100040100021080000319D005027F00504001008000041C001250000700088175010000400280010003000880000518AA027F400006850130008011020100000001030002000300040005000006
5008 }  }
5009 }  }  }".
5010
5011
5012pretty_otp5068_msg1(suite) ->
5013    [];
5014pretty_otp5068_msg1(Config) when is_list(Config) ->
5015    d("pretty_otp5068_msg1 -> entry", []),
5016    ?ACQUIRE_NODES(1, Config),
5017    Msg = pretty_otp5068_msg1(),
5018    case encode_message(megaco_pretty_text_encoder, [], Msg) of
5019	{error, Reason} ->
5020% 	    io:format("pretty_otp5068_msg1 -> "
5021% 		      "~n   Reason: ~w"
5022% 		      "~n", [Reason]),
5023	    exit({unexpected_encode_result, Reason});
5024	{ok, Bin} ->
5025% 	    io:format("pretty_otp5068_msg1 -> successfull encode:"
5026% 		      "~n~s~n", [binary_to_list(Bin)]),
5027	    case decode_message(megaco_pretty_text_encoder, false, [], Bin) of
5028		{ok, _} ->
5029% 		    io:format("pretty_otp5068_msg1 -> ok~n", []),
5030		    ok;
5031		Else ->
5032% 		    io:format("pretty_otp5068_msg1 -> ~n~p~n", [Else]),
5033		    exit({unexpected_decode_result, Else})
5034	    end
5035    end.
5036
5037pretty_otp5068_msg1() ->
5038{'MegacoMessage',
5039 asn1_NOVALUE,
5040 {'Message',
5041  2,
5042  {deviceName,[109,103,51,51]},
5043  {transactions,
5044   [{transactionReply,
5045     {'TransactionReply',
5046      190,
5047      asn1_NOVALUE,
5048      {actionReplies,
5049       [{'ActionReply',  %% Comments: This is repeated many times.
5050	 0,
5051	 asn1_NOVALUE,
5052	 asn1_NOVALUE,
5053	 [{auditValueReply,
5054	   {auditResult,
5055	    {'AuditResult',
5056	     {megaco_term_id,false,
5057	      [[99,101,100,101,118,49,47,52,47,49,47,49],[51,49]]},
5058	     [{mediaDescriptor,
5059	       {'MediaDescriptor',
5060		{'TerminationStateDescriptor',
5061		 [],
5062		 asn1_NOVALUE,
5063		 inSvc},
5064		asn1_NOVALUE}}]}}}]}]}}}]}}}.
5065
5066
5067
5068pretty_otp5085_msg1(suite) ->
5069    [];
5070pretty_otp5085_msg1(Config) when is_list(Config) ->
5071    d("pretty_otp5085_msg1 -> entry", []),
5072    ?ACQUIRE_NODES(1, Config),
5073    pretty_otp5085(ok, pretty_otp5085_msg1()).
5074
5075pretty_otp5085_msg2(suite) ->
5076    [];
5077pretty_otp5085_msg2(Config) when is_list(Config) ->
5078    d("pretty_otp5085_msg2 -> entry", []),
5079    ?ACQUIRE_NODES(1, Config),
5080    pretty_otp5085(error, pretty_otp5085_msg2()).
5081
5082pretty_otp5085_msg3(suite) ->
5083    [];
5084pretty_otp5085_msg3(Config) when is_list(Config) ->
5085    d("pretty_otp5085_msg3 -> entry", []),
5086    ?ACQUIRE_NODES(1, Config),
5087    pretty_otp5085(ok, pretty_otp5085_msg3()).
5088
5089pretty_otp5085_msg4(suite) ->
5090    [];
5091pretty_otp5085_msg4(Config) when is_list(Config) ->
5092    d("pretty_otp5085_msg4 -> entry", []),
5093    ?ACQUIRE_NODES(1, Config),
5094    pretty_otp5085(ok, pretty_otp5085_msg4()).
5095
5096pretty_otp5085_msg5(suite) ->
5097    [];
5098pretty_otp5085_msg5(Config) when is_list(Config) ->
5099    d("pretty_otp5085_msg5 -> entry", []),
5100    ?ACQUIRE_NODES(1, Config),
5101    pretty_otp5085(ok, pretty_otp5085_msg5()).
5102
5103pretty_otp5085_msg6(suite) ->
5104    [];
5105pretty_otp5085_msg6(Config) when is_list(Config) ->
5106    d("pretty_otp5085_msg6 -> entry", []),
5107    ?ACQUIRE_NODES(1, Config),
5108    pretty_otp5085(ok, pretty_otp5085_msg6()).
5109
5110pretty_otp5085_msg7(suite) ->
5111    [];
5112pretty_otp5085_msg7(Config) when is_list(Config) ->
5113    d("pretty_otp5085_msg7 -> entry", []),
5114    ?ACQUIRE_NODES(1, Config),
5115    pretty_otp5085(ok, pretty_otp5085_msg7()).
5116
5117pretty_otp5085(Expected, Msg) ->
5118    pretty_otp5085(Expected, Msg, []).
5119
5120pretty_otp5085(Expected, Msg, Conf) ->
5121    t("pretty_otp5085 -> entry with"
5122      "~n   Expected: ~p"
5123      "~n   Msg:      ~p", [Expected, Msg]),
5124    case (catch encode_message(megaco_pretty_text_encoder, Conf, Msg)) of
5125	{error, Reason} when Expected == error ->
5126 	    d("pretty_otp5085 -> encode failed as expected"
5127	      "~n   Reason: ~w", [Reason]),
5128	    ok;
5129	{error, Reason} ->
5130 	    e("pretty_otp5085 -> encode failed unexpectedly: "
5131	      "~n   Reason: ~w", [Reason]),
5132	    exit({unexpected_encode_result, Reason});
5133	{ok, Bin} when Expected == error ->
5134 	    e("pretty_otp5085 -> encode succeded unexpectedly: "
5135	      "~n   ~w", [binary_to_list(Bin)]),
5136	    exit({unexpected_encode_result, binary_to_list(Bin)});
5137	{ok, Bin} ->
5138	    d("pretty_otp5085 -> successfull encode as expected:"
5139	      "~n~s", [binary_to_list(Bin)]),
5140	    case decode_message(megaco_pretty_text_encoder, false, Conf, Bin) of
5141		{ok, Msg} ->
5142 		    d("pretty_otp5085 -> successfull decode~n", []),
5143		    ok;
5144		{ok, Msg2} ->
5145 		    e("pretty_otp5085 -> successfull decode"
5146		      " - but not equal", []),
5147		    exit({unexpected_decode_result, Msg, Msg2});
5148		Else ->
5149 		    e("pretty_otp5085 -> decode failed:~n~p", [Else]),
5150		    exit({unexpected_decode_result, Else})
5151	    end
5152    end.
5153
5154pretty_otp5085_msg1() ->
5155    {'MegacoMessage',
5156     asn1_NOVALUE,
5157     {'Message',
5158      ?VERSION,
5159      {deviceName,"mg36"},
5160      {transactions,
5161       [{transactionReply,
5162	 {'TransactionReply',
5163	  230,
5164	  asn1_NOVALUE,
5165	  {actionReplies,
5166	   [{'ActionReply',
5167	     400,
5168	     {'ErrorDescriptor',504,asn1_NOVALUE},
5169	     asn1_NOVALUE,
5170	     []
5171	    }
5172	   ]
5173	  }
5174	 }
5175	}
5176       ]
5177      }
5178     }
5179    }.
5180
5181pretty_otp5085_msg2() ->
5182    {'MegacoMessage',
5183     asn1_NOVALUE,
5184     {'Message',
5185      ?VERSION,
5186      {deviceName,"mg36"},
5187      {transactions,
5188       [{transactionReply,
5189	 {'TransactionReply',
5190	  230,
5191	  asn1_NOVALUE,
5192	  {actionReplies,
5193	   [{'ActionReply',
5194	     400,
5195	     asn1_NOVALUE,
5196	     asn1_NOVALUE,
5197	     []
5198	    }
5199	   ]
5200	  }
5201	 }
5202	}
5203       ]
5204      }
5205     }
5206    }.
5207
5208pretty_otp5085_msg3() ->
5209    {'MegacoMessage',
5210     asn1_NOVALUE,
5211     {'Message',
5212      ?VERSION,
5213      {deviceName,"mg36"},
5214      {transactions,
5215       [{transactionReply,
5216	 {'TransactionReply',
5217	  230,
5218	  asn1_NOVALUE,
5219	  {actionReplies,
5220	   [{'ActionReply',
5221	     400,
5222	     asn1_NOVALUE,
5223	     #'ContextRequest'{priority = 3},
5224	     []
5225	    }
5226	   ]
5227	  }
5228	 }
5229	}
5230       ]
5231      }
5232     }
5233    }.
5234
5235pretty_otp5085_msg4() ->
5236    {'MegacoMessage',
5237     asn1_NOVALUE,
5238     {'Message',
5239      ?VERSION,
5240      {deviceName,"mg36"},
5241      {transactions,
5242       [{transactionReply,
5243	 {'TransactionReply',
5244	  230,
5245	  asn1_NOVALUE,
5246	  {actionReplies,
5247	   [{'ActionReply',
5248	     400,
5249	     asn1_NOVALUE,
5250	     asn1_NOVALUE,
5251	     [{addReply,    cre_AmmsReply([#megaco_term_id{id = ?A4444}])},
5252	      {notifyReply, cre_NotifyRep([#megaco_term_id{id = ?A5555}])}]
5253	    }
5254	   ]
5255	  }
5256	 }
5257	}
5258       ]
5259      }
5260     }
5261    }.
5262
5263pretty_otp5085_msg5() ->
5264    {'MegacoMessage',
5265     asn1_NOVALUE,
5266     {'Message',
5267      ?VERSION,
5268      {deviceName,"mg36"},
5269      {transactions,
5270       [{transactionReply,
5271	 {'TransactionReply',
5272	  230,
5273	  asn1_NOVALUE,
5274	  {actionReplies,
5275	   [{'ActionReply',
5276	     400,
5277	     asn1_NOVALUE,
5278	     #'ContextRequest'{priority = 5},
5279	     [{addReply,    cre_AmmsReply([#megaco_term_id{id = ?A4444}])},
5280	      {notifyReply, cre_NotifyRep([#megaco_term_id{id = ?A5555}])}]
5281	    }
5282	   ]
5283	  }
5284	 }
5285	}
5286       ]
5287      }
5288     }
5289    }.
5290
5291pretty_otp5085_msg6() ->
5292    {'MegacoMessage',
5293     asn1_NOVALUE,
5294     {'Message',
5295      ?VERSION,
5296      {deviceName,"msg36"},
5297      {transactions,
5298       [{transactionReply,
5299	 {'TransactionReply',
5300	  230,
5301	  asn1_NOVALUE,
5302	  {actionReplies,
5303	   [{'ActionReply',
5304	     400,
5305	     {'ErrorDescriptor',504,asn1_NOVALUE},
5306	     #'ContextRequest'{priority = 6},
5307	     [{addReply,    cre_AmmsReply([#megaco_term_id{id = ?A4444}])},
5308	      {notifyReply, cre_NotifyRep([#megaco_term_id{id = ?A5555}])}]
5309	    }
5310	   ]
5311	  }
5312	 }
5313	}
5314       ]
5315      }
5316     }
5317    }.
5318
5319pretty_otp5085_msg7() ->
5320    {'MegacoMessage',
5321     asn1_NOVALUE,
5322     {'Message',
5323      ?VERSION,
5324      {deviceName,"msg36"},
5325      {transactions,
5326       [{transactionReply,
5327	 {'TransactionReply',
5328	  230,
5329	  asn1_NOVALUE,
5330	  {actionReplies,
5331	   [{'ActionReply',
5332	     400,
5333	     {'ErrorDescriptor',504,asn1_NOVALUE},
5334	     #'ContextRequest'{priority = 7},
5335	     [{notifyReply, cre_NotifyRep([#megaco_term_id{id = ?A5555}])}]
5336	    }
5337	   ]
5338	  }
5339	 }
5340	}
5341       ]
5342      }
5343     }
5344    }.
5345
5346
5347
5348pretty_otp5600_msg1(suite) ->
5349    [];
5350pretty_otp5600_msg1(Config) when is_list(Config) ->
5351    d("pretty_otp5600_msg1 -> entry", []),
5352    ?ACQUIRE_NODES(1, Config),
5353    %%     put(severity,trc),
5354    %%     put(dbg,true),
5355    pretty_otp5600(ok, pretty_otp5600_msg1()).
5356
5357pretty_otp5600_msg2(suite) ->
5358    [];
5359pretty_otp5600_msg2(Config) when is_list(Config) ->
5360    d("pretty_otp5600_msg2 -> entry", []),
5361    ?ACQUIRE_NODES(1, Config),
5362    %%     put(severity,trc),
5363    %%     put(dbg,true),
5364    pretty_otp5600(ok, pretty_otp5600_msg2()).
5365
5366pretty_otp5600(Expected, Msg) ->
5367    pretty_otp5600(Expected, Msg, []).
5368
5369pretty_otp5600(Expected, Msg, Conf) ->
5370    t("pretty_otp5600 -> entry with"
5371      "~n   Expected: ~p"
5372      "~n   Msg:      ~p", [Expected, Msg]),
5373    case (catch encode_message(megaco_pretty_text_encoder, Conf, Msg)) of
5374	{error, Reason} when Expected == error ->
5375 	    d("pretty_otp5600 -> encode failed as expected"
5376	      "~n   Reason: ~w", [Reason]),
5377	    ok;
5378	{error, Reason} ->
5379 	    e("pretty_otp5600 -> encode failed unexpectedly: "
5380	      "~n   Reason: ~w", [Reason]),
5381	    exit({unexpected_encode_result, Reason});
5382	{ok, Bin} when Expected == error ->
5383 	    e("pretty_otp5600 -> encode succeded unexpectedly: "
5384	      "~n   ~w", [binary_to_list(Bin)]),
5385	    exit({unexpected_encode_result, binary_to_list(Bin)});
5386	{ok, Bin} ->
5387	    d("pretty_otp5600 -> successfull encode as expected:"
5388	      "~n~s", [binary_to_list(Bin)]),
5389	    case decode_message(megaco_pretty_text_encoder, false, Conf, Bin) of
5390		{ok, Msg} ->
5391 		    d("pretty_otp5600 -> successfull decode~n", []),
5392		    ok;
5393		{ok, Msg2} ->
5394 		    e("pretty_otp5600 -> successfull decode"
5395		      " - but not equal", []),
5396		    exit({unexpected_decode_result, Msg, Msg2});
5397		Else ->
5398 		    e("pretty_otp5600 -> decode failed:~n~p", [Else]),
5399		    exit({unexpected_decode_result, Else})
5400	    end
5401    end.
5402
5403
5404pretty_otp5600_msg1() ->
5405    SRE = #'SecondRequestedEvent'{ pkgdName = "al/on",
5406				   evParList = [] },
5407
5408    SED = #'SecondEventsDescriptor'{ requestID = 2,
5409				     eventList = [ SRE ] },
5410
5411    SIG = { signal, #'Signal'{ signalName = "cg/dt",
5412			       sigParList = [] } },
5413
5414    RA = #'RequestedActions'{ secondEvent = SED,
5415			      signalsDescriptor = [ SIG ] },
5416
5417    RE = #'RequestedEvent'{ pkgdName = "al/of",
5418			    eventAction = RA,
5419			    evParList = [] },
5420
5421    EV = #'EventsDescriptor'{ requestID = 1, eventList = [ RE ] },
5422
5423    TermID = {megaco_term_id, true, [[$*]] },
5424
5425    AMMR = #'AmmRequest'{ terminationID = [ TermID ],
5426			  descriptors = [ { eventsDescriptor, EV } ] },
5427
5428    CR = #'CommandRequest'{command = {modReq, AMMR}},
5429
5430    AR = #'ActionRequest'{contextId = ?megaco_null_context_id,
5431			  commandRequests = [CR]},
5432    ARs = [AR],
5433    TR = #'TransactionRequest'{transactionId = 5600, actions = ARs},
5434    TRs = [{transactionRequest, TR}],
5435    Mess = #'Message'{version = ?VERSION,
5436		      mId = ?MGC_MID,
5437		      messageBody = {transactions, TRs}},
5438    #'MegacoMessage'{mess = Mess}.
5439
5440
5441pretty_otp5600_msg2() ->
5442    SIG = { signal, #'Signal'{ signalName = "cg/dt",
5443			       sigParList = [] } },
5444
5445    SRA = #'SecondRequestedActions'{ signalsDescriptor = [ SIG ] },
5446
5447    SRE = #'SecondRequestedEvent'{ pkgdName    = "al/on",
5448				   eventAction = SRA,
5449				   evParList   = [] },
5450
5451    SED = #'SecondEventsDescriptor'{ requestID = 2,
5452				     eventList = [ SRE ] },
5453
5454    RA = #'RequestedActions'{ secondEvent = SED },
5455
5456    RE = #'RequestedEvent'{ pkgdName = "al/of",
5457			    eventAction = RA,
5458			    evParList = [] },
5459
5460    EV = #'EventsDescriptor'{ requestID = 1, eventList = [ RE ] },
5461
5462    TermID = {megaco_term_id, true, [[$*]] },
5463
5464    AMMR = #'AmmRequest'{ terminationID = [ TermID ],
5465			  descriptors = [ { eventsDescriptor, EV } ] },
5466
5467    CR = #'CommandRequest'{command = {modReq, AMMR}},
5468
5469    AR = #'ActionRequest'{contextId = ?megaco_null_context_id,
5470			  commandRequests = [CR]},
5471    ARs = [AR],
5472    TR = #'TransactionRequest'{transactionId = 5600, actions = ARs},
5473    TRs = [{transactionRequest, TR}],
5474    Mess = #'Message'{version = ?VERSION,
5475		      mId = ?MGC_MID,
5476		      messageBody = {transactions, TRs}},
5477    #'MegacoMessage'{mess = Mess}.
5478
5479
5480pretty_otp5601_msg1(suite) ->
5481    [];
5482pretty_otp5601_msg1(Config) when is_list(Config) ->
5483    d("pretty_otp5601_msg1 -> entry", []),
5484    ?ACQUIRE_NODES(1, Config),
5485    %% put(severity,trc),
5486    %% put(dbg,true),
5487    pretty_otp5601(ok, pretty_otp5601_msg1()).
5488
5489pretty_otp5601(Expected, Msg) ->
5490    pretty_otp5601(Expected, Msg, []).
5491
5492pretty_otp5601(Expected, Msg, Conf) ->
5493    t("pretty_otp5601 -> entry with"
5494      "~n   Expected: ~p"
5495      "~n   Msg:      ~p", [Expected, Msg]),
5496    case (catch encode_message(megaco_pretty_text_encoder, Conf, Msg)) of
5497	{error, Reason} when Expected == error ->
5498 	    d("pretty_otp5601 -> encode failed as expected"
5499	      "~n   Reason: ~w", [Reason]),
5500	    ok;
5501	{error, Reason} ->
5502 	    e("pretty_otp5601 -> encode failed unexpectedly: "
5503	      "~n   Reason: ~w", [Reason]),
5504	    exit({unexpected_encode_result, Reason});
5505	{ok, Bin} when Expected == error ->
5506 	    e("pretty_otp5601 -> encode succeded unexpectedly: "
5507	      "~n   ~w", [binary_to_list(Bin)]),
5508	    exit({unexpected_encode_result, binary_to_list(Bin)});
5509	{ok, Bin} ->
5510	    d("pretty_otp5601 -> successfull encode as expected:"
5511	      "~n~s", [binary_to_list(Bin)]),
5512	    case decode_message(megaco_pretty_text_encoder, false, Conf, Bin) of
5513		{ok, Msg} ->
5514 		    d("pretty_otp5601 -> successfull decode~n", []),
5515		    ok;
5516		{ok, Msg2} ->
5517 		    e("pretty_otp5601 -> successfull decode"
5518		      " - but not equal", []),
5519		    exit({unexpected_decode_result, Msg, Msg2});
5520		Else ->
5521 		    e("pretty_otp5601 -> decode failed:~n~p", [Else]),
5522		    exit({unexpected_decode_result, Else})
5523	    end
5524    end.
5525
5526pretty_otp5601_msg1() ->
5527    SRE1 = #'SecondRequestedEvent'{ pkgdName = "al/on",
5528				    evParList = [] },
5529
5530    SRA = #'SecondRequestedActions'{ eventDM = { digitMapName, "dialllan0" }},
5531
5532    SRE2 = #'SecondRequestedEvent'{ pkgdName = "dd/ce",
5533				    eventAction = SRA,
5534				    evParList = [] },
5535
5536    SED = #'SecondEventsDescriptor'{ requestID = 2,
5537				     eventList = [ SRE1, SRE2 ] },
5538
5539    RA = #'RequestedActions'{ secondEvent = SED },
5540
5541    RE = #'RequestedEvent'{ pkgdName = "al/of",
5542			    eventAction = RA,
5543			    evParList = [] },
5544
5545    EV = #'EventsDescriptor'{ requestID = 1, eventList = [ RE ] },
5546
5547    TermID = {megaco_term_id, true, [[$*]] },
5548
5549    AMMR = #'AmmRequest'{ terminationID = [ TermID ],
5550			  descriptors = [ { eventsDescriptor, EV } ] },
5551
5552    CR = #'CommandRequest'{command = {modReq, AMMR}},
5553
5554    AR = #'ActionRequest'{contextId = ?megaco_null_context_id,
5555			  commandRequests = [CR]},
5556    ARs = [AR],
5557    TR = #'TransactionRequest'{transactionId = 5600, actions = ARs},
5558    TRs = [{transactionRequest, TR}],
5559    Mess = #'Message'{version = ?VERSION,
5560		      mId = ?MGC_MID,
5561		      messageBody = {transactions, TRs}},
5562    #'MegacoMessage'{mess = Mess}.
5563
5564
5565pretty_otp5793_msg01(suite) ->
5566    [];
5567pretty_otp5793_msg01(Config) when is_list(Config) ->
5568    d("pretty_otp5793_msg01 -> entry", []),
5569    ?ACQUIRE_NODES(1, Config),
5570%%     put(severity,trc),
5571%%     put(dbg,true),
5572    pretty_otp5793(ok, pretty_otp5793_msg1()).
5573
5574pretty_otp5793(Expected, Msg) ->
5575    expect_codec(Expected, megaco_pretty_text_encoder, Msg, []).
5576
5577pretty_otp5793(Expected, Msg, Conf) ->
5578    expect_codec(Expected, megaco_pretty_text_encoder, Msg, Conf).
5579
5580
5581pretty_otp5793_msg1() ->
5582    {'MegacoMessage',asn1_NOVALUE,
5583     {'Message',2,
5584      {deviceName,"bs_sbg_4/99"},
5585      {transactions,
5586       [{transactionReply,
5587	 {'TransactionReply',
5588	  370,
5589	  asn1_NOVALUE,
5590	  {actionReplies,
5591	   [{'ActionReply',
5592	     3,
5593	     asn1_NOVALUE,
5594	     asn1_NOVALUE,
5595	     [{auditValueReply,
5596	       {contextAuditResult,
5597		[{megaco_term_id,
5598		  false,
5599		  ["ip",
5600		   "104",
5601		   "1",
5602		   "18"]}]}},
5603	      {auditValueReply,
5604	       {contextAuditResult,
5605		[{megaco_term_id,
5606		  false,
5607		  ["ip",
5608		   "104",
5609		   "2",
5610		   "19"]}]}}]}]}}}]}}}.
5611
5612
5613pretty_otp5882_msg01(suite) ->
5614    [];
5615pretty_otp5882_msg01(Config) when is_list(Config) ->
5616    d("pretty_otp5882_msg01 -> entry", []),
5617    ?ACQUIRE_NODES(1, Config),
5618    %% put(severity,trc),
5619    %% put(dbg,true),
5620    pretty_otp5882().
5621
5622pretty_otp5882() ->
5623    otp5882(megaco_pretty_text_encoder, []).
5624
5625otp5882(Codec, Conf) ->
5626    Msg  = pretty_otp5882_msg01(),
5627    case (catch encode_message(Codec, Conf, Msg)) of
5628	{error, {message_encode_failed, {error, {ActualReason, _}}, _}} ->
5629	    case ActualReason of
5630		{invalid_LocalControlDescriptor, empty} ->
5631		    ok;
5632		_ ->
5633		    exit({unexpected_error_actual_reason, ActualReason})
5634	    end;
5635	{error, Reason} ->
5636	    exit({unexpected_error_reason, Reason});
5637	{ok, Bin} ->
5638	    exit({unexpected_encode_sucess, binary_to_list(Bin)})
5639    end.
5640
5641pretty_otp5882_msg01() ->
5642    LCD = #'LocalControlDescriptor'{}, % Create illegal LCD
5643    Parms      = ?MSG_LIB:cre_StreamParms(LCD),
5644    StreamDesc = ?MSG_LIB:cre_StreamDescriptor(1, Parms),
5645    MediaDesc  = ?MSG_LIB:cre_MediaDescriptor([StreamDesc]),
5646    AmmReq     = ?MSG_LIB:cre_AmmRequest([#megaco_term_id{id = ?A4445}],
5647					 [{mediaDescriptor, MediaDesc}]),
5648    Cmd        = ?MSG_LIB:cre_Command(modReq, AmmReq),
5649    CmdReq     = ?MSG_LIB:cre_CommandRequest(Cmd),
5650    CID        = ?MSG_LIB:cre_ContextID(5882),
5651    ActReq     = ?MSG_LIB:cre_ActionRequest(CID, [CmdReq]),
5652    Actions    = [ActReq],
5653    TransId    = ?MSG_LIB:cre_TransactionId(7302),
5654    TransReq   = ?MSG_LIB:cre_TransactionRequest(TransId, Actions),
5655    Trans      = ?MSG_LIB:cre_Transaction(TransReq),
5656    Mid        = ?MG1_MID,
5657    Mess       = ?MSG_LIB:cre_Message(?VERSION, Mid, [Trans]),
5658    ?MSG_LIB:cre_MegacoMessage(Mess).
5659
5660
5661%% --------------------------------------------------------------
5662%%
5663pretty_otp6490_msg01(suite) ->
5664    [];
5665pretty_otp6490_msg01(Config) when is_list(Config) ->
5666    %% put(severity, trc),
5667    %% put(dbg,      true),
5668    d("pretty_otp6490_msg01 -> entry", []),
5669    %% ?ACQUIRE_NODES(1, Config),
5670    ok = pretty_otp6490( pretty_otp6490_msg01(), [] ),
5671    %% erase(dbg),
5672    %% erase(severity),
5673    ok.
5674
5675pretty_otp6490_msg02(suite) ->
5676    [];
5677pretty_otp6490_msg02(Config) when is_list(Config) ->
5678    %% put(severity, trc),
5679    %% put(dbg,      true),
5680    d("pretty_otp6490_msg02 -> entry", []),
5681    %% ?ACQUIRE_NODES(1, Config),
5682    ok = pretty_otp6490( pretty_otp6490_msg02(), [] ),
5683    %% erase(severity),
5684    %% erase(dbg),
5685    ok.
5686
5687pretty_otp6490_msg03(suite) ->
5688    [];
5689pretty_otp6490_msg03(Config) when is_list(Config) ->
5690    %% put(severity, trc),
5691    %% put(dbg,      true),
5692    d("pretty_otp6490_msg03 -> entry", []),
5693    %% ?ACQUIRE_NODES(1, Config),
5694    ok = pretty_otp6490( pretty_otp6490_msg03(), [] ),
5695    %% erase(severity),
5696    %% erase(dbg),
5697    ok.
5698
5699pretty_otp6490_msg04(suite) ->
5700    [];
5701pretty_otp6490_msg04(Config) when is_list(Config) ->
5702    %% put(severity, trc),
5703    %% put(dbg,      true),
5704    d("pretty_otp6490_msg04 -> entry", []),
5705    %% ?ACQUIRE_NODES(1, Config),
5706    ok = pretty_otp6490( pretty_otp6490_msg04(), [] ),
5707    %% erase(severity),
5708    %% erase(dbg),
5709    ok.
5710
5711pretty_otp6490_msg05(suite) ->
5712    [];
5713pretty_otp6490_msg05(Config) when is_list(Config) ->
5714    %% put(severity, trc),
5715    %% put(dbg,      true),
5716    d("pretty_otp6490_msg05 -> entry", []),
5717    %% ?ACQUIRE_NODES(1, Config),
5718    ok = pretty_otp6490( pretty_otp6490_msg05(), [] ),
5719    %% erase(severity),
5720    %% erase(dbg),
5721    ok.
5722
5723pretty_otp6490_msg06(suite) ->
5724    [];
5725pretty_otp6490_msg06(Config) when is_list(Config) ->
5726    %% put(severity, trc),
5727    %% put(dbg,      true),
5728    d("pretty_otp6490_msg06 -> entry", []),
5729    %% ?ACQUIRE_NODES(1, Config),
5730    ok = pretty_otp6490( pretty_otp6490_msg06(), [] ),
5731    %% erase(severity),
5732    %% erase(dbg),
5733    ok.
5734
5735pretty_otp6490(Msg, Conf) ->
5736    pretty_otp6490(Msg, Conf, ok).
5737
5738pretty_otp6490(Msg, Conf, ExpectedEncode) ->
5739    pretty_otp6490(Msg, Conf, ExpectedEncode, ok).
5740
5741pretty_otp6490(Msg, Conf, ExpectedEncode, ExpectedDecode) ->
5742    otp6490(Msg, megaco_pretty_text_encoder, Conf,
5743	    ExpectedEncode, ExpectedDecode).
5744
5745otp6490(Msg, Codec, Conf, ExpectedEncode, ExpectedDecode) ->
5746    case (catch encode_message(Codec, Conf, Msg)) of
5747	{error, _Reason} when ExpectedEncode == error ->
5748	    ok;
5749	{error, Reason} when ExpectedEncode == ok ->
5750	    exit({unexpected_encode_failure, Reason});
5751	{ok, Bin} when ExpectedEncode == error ->
5752	    exit({unexpected_encode_success, Msg, binary_to_list(Bin)});
5753	{ok, Bin} when ExpectedEncode == ok ->
5754	    case decode_message(Codec, false, Conf, Bin) of
5755		{ok, Msg} when ExpectedDecode == ok ->
5756		    ok;
5757		{ok, Msg} when ExpectedDecode == error ->
5758		    exit({unexpected_decode_success, Msg});
5759		{ok, Msg2} when ExpectedDecode == ok ->
5760		    exit({unexpected_decode_result, Msg, Msg2});
5761		{ok, Msg2} when ExpectedDecode == error ->
5762		    exit({unexpected_decode_success, Msg, Msg2});
5763		{error, _Reason} when ExpectedDecode == error ->
5764		    ok;
5765		{error, Reason} when ExpectedDecode == ok ->
5766		    exit({unexpected_decode_failure, Msg, Reason})
5767	    end
5768    end.
5769
5770
5771pretty_otp6490_msg(EBD) ->
5772    AmmDesc    = ?MSG_LIB:cre_AmmDescriptor(EBD),
5773    AmmReq     = cre_AmmReq([#megaco_term_id{id = ?A4445}], [AmmDesc]),
5774    CmdReq     = cre_CmdReq({modReq, AmmReq}),
5775    CID        = cre_CtxID(64901),
5776    ActReq     = cre_ActReq(CID, [CmdReq]),
5777    Actions    = [ActReq],
5778    TransId    = cre_TransId(64902),
5779    TransReq   = cre_TransReq(TransId, Actions),
5780    Trans      = cre_Trans(TransReq),
5781    Mid        = ?MG1_MID,
5782    Mess       = cre_Msg(Mid, [Trans]),
5783    cre_MegacoMessage(Mess).
5784
5785pretty_otp6490_msg01() ->
5786    EvSpecs = [], % This will result in an error
5787    EBD     = EvSpecs, % This is because the lib checks that the size is valid
5788    pretty_otp6490_msg(EBD).
5789
5790pretty_otp6490_msg02() ->
5791    EvPar    = ?MSG_LIB:cre_EventParameter("sune", ["mangs"]),
5792    PkgdName = ?MSG_LIB:cre_PkgdName("foo", "a"),
5793    EvName   = ?MSG_LIB:cre_EventName(PkgdName),
5794    EvSpec   = ?MSG_LIB:cre_EventSpec(EvName, [EvPar]),
5795    EvSpecs  = [EvSpec],
5796    EBD      = ?MSG_LIB:cre_EventBufferDescriptor(EvSpecs),
5797    pretty_otp6490_msg(EBD).
5798
5799pretty_otp6490_msg03() ->
5800    EvPar1   = ?MSG_LIB:cre_EventParameter("sune",   ["mangs"]),
5801    EvPar2   = ?MSG_LIB:cre_EventParameter("kalle",  ["anka"]),
5802    EvPar3   = ?MSG_LIB:cre_EventParameter("flippa", ["ur"]),
5803    PkgdName = ?MSG_LIB:cre_PkgdName("foo", "a"),
5804    EvName   = ?MSG_LIB:cre_EventName(PkgdName),
5805    EvSpec   = ?MSG_LIB:cre_EventSpec(EvName, [EvPar1,EvPar2,EvPar3]),
5806    EvSpecs  = [EvSpec],
5807    EBD      = ?MSG_LIB:cre_EventBufferDescriptor(EvSpecs),
5808    pretty_otp6490_msg(EBD).
5809
5810pretty_otp6490_msg04() ->
5811    EvPar1    = ?MSG_LIB:cre_EventParameter("sune",   ["mangs"]),
5812    EvPar2    = ?MSG_LIB:cre_EventParameter("kalle",  ["anka"]),
5813    EvPar3    = ?MSG_LIB:cre_EventParameter("flippa", ["ur"]),
5814    PkgdName1 = ?MSG_LIB:cre_PkgdName("foo", "a"),
5815    EvName1   = ?MSG_LIB:cre_EventName(PkgdName1),
5816    EvSpec1   = ?MSG_LIB:cre_EventSpec(EvName1, [EvPar1,EvPar2,EvPar3]),
5817    EvPar4    = ?MSG_LIB:cre_EventParameter("hej",    ["hopp"]),
5818    PkgdName2 = ?MSG_LIB:cre_PkgdName("bar", "b"),
5819    EvName2   = ?MSG_LIB:cre_EventName(PkgdName2),
5820    EvSpec2   = ?MSG_LIB:cre_EventSpec(EvName2, [EvPar4]),
5821    EvSpecs   = [EvSpec1,EvSpec2],
5822    EBD       = ?MSG_LIB:cre_EventBufferDescriptor(EvSpecs),
5823    pretty_otp6490_msg(EBD).
5824
5825pretty_otp6490_msg05() ->
5826    EvPar    = ?MSG_LIB:cre_EventParameter("sune", ["mangs"]),
5827    PkgdName = ?MSG_LIB:cre_PkgdName("foo", root),
5828    EvName   = ?MSG_LIB:cre_EventName(PkgdName),
5829    EvSpec   = ?MSG_LIB:cre_EventSpec(EvName, [EvPar]),
5830    EvSpecs  = [EvSpec],
5831    EBD      = ?MSG_LIB:cre_EventBufferDescriptor(EvSpecs),
5832    pretty_otp6490_msg(EBD).
5833
5834pretty_otp6490_msg06() ->
5835    EvPar    = ?MSG_LIB:cre_EventParameter("sune", ["mangs"]),
5836    PkgdName = ?MSG_LIB:cre_PkgdName(root, root),
5837    EvName   = ?MSG_LIB:cre_EventName(PkgdName),
5838    EvSpec   = ?MSG_LIB:cre_EventSpec(EvName, [EvPar]),
5839    EvSpecs  = [EvSpec],
5840    EBD      = ?MSG_LIB:cre_EventBufferDescriptor(EvSpecs),
5841    pretty_otp6490_msg(EBD).
5842
5843
5844%% --------------------------------------------------------------
5845%%
5846pretty_otp7249_msg01(suite) ->
5847    [];
5848pretty_otp7249_msg01(doc) ->
5849    "Ticket OTP-7249 has really nothing to to with just version 2 "
5850	"although the test message is version 2. Instead the decode "
5851	"is actually done by the mini decoder, which is where the bug "
5852	"manifests itself. The bug is in effect located in the (plain) "
5853	"text scanner. ";
5854pretty_otp7249_msg01(Config) when is_list(Config) ->
5855    %% put(severity, trc),
5856    %% put(dbg,      true),
5857    d("pretty_otp7249_msg01 -> entry", []),
5858    ok = pretty_otp7249( pretty_otp7249_msg01() ),
5859    %% erase(dbg),
5860    %% erase(severity),
5861    ok.
5862
5863
5864pretty_otp7249_msg01() ->
5865    "MEGACO/2 <AGW95_DCT_2_DPNSS>\r\nTransaction = 500017 { \r\nContext =  - { ServiceChange = ROOT { Services { \r\nMethod =  Disconnected, Reason =  900, 20070116T15233997 } \r\n }  }  } \r\n".
5866
5867pretty_otp7249(EncodedMsg) ->
5868    Codec = megaco_pretty_text_encoder,
5869    Conf  = [],
5870    Bin   = list_to_binary(EncodedMsg),
5871    case decode_mini_message(Codec, Conf, Bin) of
5872	{ok, Msg} when is_record(Msg, 'MegacoMessage') ->
5873	    %% 	    io:format("Msg: ~n~p"
5874	    %% 		      "~n", [Msg]),
5875	    ok;
5876	{error, Reason} ->
5877	    exit({unexpected_decode_failure, EncodedMsg, Reason})
5878    end.
5879
5880
5881
5882%% --------------------------------------------------------------
5883%%
5884
5885pretty_otp7671_msg01(suite) ->
5886    [];
5887pretty_otp7671_msg01(Config) when is_list(Config) ->
5888%%     put(severity, trc),
5889%%     put(dbg,      true),
5890    d("pretty_otp7671_msg01 -> entry", []),
5891    %% ?ACQUIRE_NODES(1, Config),
5892    ok = pretty_otp7671( pretty_otp7671_msg01(), [] ),
5893%%     erase(dbg),
5894%%     erase(severity),
5895    ok.
5896
5897pretty_otp7671_msg02(suite) ->
5898    [];
5899pretty_otp7671_msg02(Config) when is_list(Config) ->
5900%%     put(severity, trc),
5901%%     put(dbg,      true),
5902    d("pretty_otp7671_msg02 -> entry", []),
5903    %% ?ACQUIRE_NODES(1, Config),
5904    ok = pretty_otp7671( pretty_otp7671_msg02(), [] ),
5905%%     erase(dbg),
5906%%     erase(severity),
5907    ok.
5908
5909pretty_otp7671_msg03(suite) ->
5910    [];
5911pretty_otp7671_msg03(Config) when is_list(Config) ->
5912%%     put(severity, trc),
5913%%     put(dbg,      true),
5914    d("pretty_otp7671_msg03 -> entry", []),
5915    %% ?ACQUIRE_NODES(1, Config),
5916    ok = pretty_otp7671( pretty_otp7671_msg03(), [] ),
5917%%     erase(dbg),
5918%%     erase(severity),
5919    ok.
5920
5921pretty_otp7671_msg04(suite) ->
5922    [];
5923pretty_otp7671_msg04(Config) when is_list(Config) ->
5924%%     put(severity, trc),
5925%%     put(dbg,      true),
5926    d("pretty_otp7671_msg04 -> entry", []),
5927    %% ?ACQUIRE_NODES(1, Config),
5928    ok = pretty_otp7671( pretty_otp7671_msg04(), [] , error, ignore),
5929%%     erase(dbg),
5930%%     erase(severity),
5931    ok.
5932
5933pretty_otp7671_msg05(suite) ->
5934    [];
5935pretty_otp7671_msg05(Config) when is_list(Config) ->
5936%%     put(severity, trc),
5937%%     put(dbg,      true),
5938    d("pretty_otp7671_msg05 -> entry", []),
5939    Check = fun(M1, M2) -> cmp_otp7671_msg05(M1, M2) end,
5940    ok = pretty_otp7671( pretty_otp7671_msg05(), [] , ok, ok, Check),
5941%%     erase(dbg),
5942%%     erase(severity),
5943    ok.
5944
5945
5946pretty_otp7671(Msg, Conf) ->
5947    pretty_otp7671(Msg, Conf, ok).
5948
5949pretty_otp7671(Msg, Conf, ExpectedEncode) ->
5950    pretty_otp7671(Msg, Conf, ExpectedEncode, ok).
5951
5952pretty_otp7671(Msg, Conf, ExpectedEncode, ExpectedDecode) ->
5953    otp7671(Msg, megaco_pretty_text_encoder, Conf,
5954            ExpectedEncode, ExpectedDecode).
5955
5956pretty_otp7671(Msg, Conf, ExpectedEncode, ExpectedDecode, Check) ->
5957    otp7671(Msg, megaco_pretty_text_encoder, Conf,
5958            ExpectedEncode, ExpectedDecode, Check).
5959
5960otp7671(Msg, Codec, Conf, ExpectedEncode, ExpectedDecode) ->
5961    Check = fun(M1, M2) ->
5962		    exit({unexpected_decode_result, M1, M2})
5963	    end,
5964    otp7671(Msg, Codec, Conf, ExpectedEncode, ExpectedDecode, Check).
5965
5966otp7671(Msg, Codec, Conf, ExpectedEncode, ExpectedDecode, Check)
5967  when is_function(Check) ->
5968    case (catch encode_message(Codec, Conf, Msg)) of
5969        {error, _Reason} when ExpectedEncode =:= error ->
5970            ok;
5971        {error, Reason} when ExpectedEncode =:= ok ->
5972            exit({unexpected_encode_failure, Reason});
5973        {ok, Bin} when ExpectedEncode =:= error ->
5974            exit({unexpected_encode_success, Msg, binary_to_list(Bin)});
5975        {ok, Bin} when ExpectedEncode =:= ok ->
5976            case decode_message(Codec, false, Conf, Bin) of
5977                {ok, Msg} when ExpectedDecode =:= ok ->
5978                    ok;
5979                {ok, Msg2} when ExpectedDecode =:= ok ->
5980		    Check(Msg, Msg2);
5981                {ok, Msg} when ExpectedDecode =:= error ->
5982                    exit({unexpected_decode_success, Msg});
5983                {ok, Msg2} when ExpectedDecode =:= error ->
5984                    exit({unexpected_decode_success, Msg, Msg2});
5985                {error, _Reason} when ExpectedDecode =:= error ->
5986                    ok;
5987                {error, Reason} when ExpectedDecode == ok ->
5988                    exit({unexpected_decode_failure, Msg, Reason})
5989            end
5990    end.
5991
5992
5993pretty_otp7671_msg(DigitMapDesc) ->
5994    AmmReq = cre_AmmReq([#megaco_term_id{id = ["root"]}],
5995			[{digitMapDescriptor, DigitMapDesc}]),
5996    CmdReq = cre_CmdReq({modReq, AmmReq}),
5997    msg_request(?MGC_MID, 10001, ?megaco_null_context_id, [CmdReq]).
5998
5999pretty_otp7671_msg01() ->
6000    Name         = "dialplan01",
6001    DigitMapDesc = cre_DigitMapDesc(Name),
6002    pretty_otp7671_msg(DigitMapDesc).
6003
6004pretty_otp7671_msg02() ->
6005    Name         = "dialplan02",
6006    Body         = "(0s| 00s|[1-7]xlxx|8lxxxxxxx|#xxxxxxx|*xx|9l1xxxxxxxxxx|9l011x.s)",
6007    Value        = cre_DigitMapValue(Body),
6008    DigitMapDesc = cre_DigitMapDesc(Name, Value),
6009    pretty_otp7671_msg(DigitMapDesc).
6010
6011pretty_otp7671_msg03() ->
6012    Body         = "(0s| 00s|[1-7]xlxx|8lxxxxxxx|#xxxxxxx|*xx|9l1xxxxxxxxxx|9l011x.s)",
6013    Value        = cre_DigitMapValue(Body),
6014    DigitMapDesc = cre_DigitMapDesc(Value),
6015    pretty_otp7671_msg(DigitMapDesc).
6016
6017pretty_otp7671_msg04() ->
6018    DigitMapDesc = cre_DigitMapDesc(),
6019    pretty_otp7671_msg(DigitMapDesc).
6020
6021pretty_otp7671_msg05() ->
6022    {'MegacoMessage',asn1_NOVALUE,
6023     {'Message',?VERSION,
6024      {domainName,{'DomainName',"tgc",asn1_NOVALUE}},
6025      {transactions,
6026       [{transactionRequest,
6027	 {'TransactionRequest',12582952,
6028	  [{'ActionRequest',0,asn1_NOVALUE,asn1_NOVALUE,
6029	    [{'CommandRequest',
6030	      {modReq,
6031	       {'AmmRequest',
6032		[{megaco_term_id,false,["root"]}],
6033		[{digitMapDescriptor,
6034		  {'DigitMapDescriptor',"dialplan1",
6035		   {'DigitMapValue',asn1_NOVALUE,asn1_NOVALUE,asn1_NOVALUE,[],
6036		    asn1_NOVALUE}}}]}},
6037	      asn1_NOVALUE,asn1_NOVALUE}]}]}}]}}}.
6038
6039cmp_otp7671_msg05(#'MegacoMessage'{authHeader = asn1_NOVALUE,
6040				   mess       = M1},
6041		  #'MegacoMessage'{authHeader = asn1_NOVALUE,
6042				   mess       = M2}) ->
6043    #'Message'{messageBody = Body1} = M1,
6044    #'Message'{messageBody = Body2} = M2,
6045    {transactions, Trans1} = Body1,
6046    {transactions, Trans2} = Body2,
6047    [{transactionRequest, TR1}] = Trans1,
6048    [{transactionRequest, TR2}] = Trans2,
6049    #'TransactionRequest'{actions = Acts1} = TR1,
6050    #'TransactionRequest'{actions = Acts2} = TR2,
6051    [#'ActionRequest'{commandRequests = CR1}] = Acts1,
6052    [#'ActionRequest'{commandRequests = CR2}] = Acts2,
6053    [#'CommandRequest'{command = Cmd1}] = CR1,
6054    [#'CommandRequest'{command = Cmd2}] = CR2,
6055    {modReq, #'AmmRequest'{descriptors = Descs1}} = Cmd1,
6056    {modReq, #'AmmRequest'{descriptors = Descs2}} = Cmd2,
6057    [{digitMapDescriptor,
6058      #'DigitMapDescriptor'{digitMapName = Name,
6059			    digitMapValue = Value1}}] = Descs1,
6060    [{digitMapDescriptor,
6061      #'DigitMapDescriptor'{digitMapName = Name,
6062			    digitMapValue = Value2}}] = Descs2,
6063    #'DigitMapValue'{startTimer    = asn1_NOVALUE,
6064		     shortTimer    = asn1_NOVALUE,
6065		     longTimer     = asn1_NOVALUE,
6066		     digitMapBody  = [],
6067		     durationTimer = asn1_NOVALUE} = Value1,
6068    asn1_NOVALUE = Value2,
6069    ok.
6070
6071
6072%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
6073
6074expect_codec(Expect, Codec, Msg, Conf) ->
6075    t("expect_codec -> entry with"
6076      "~n   Expect: ~p"
6077      "~n   Msg:    ~p", [Expect, Msg]),
6078    case (catch encode_message(Codec, Conf, Msg)) of
6079	{error, _Reason} when Expect == error ->
6080 	    d("expect_codec -> encode failed as expected"
6081	      "~n   _Reason: ~w", [_Reason]),
6082	    ok;
6083	{error, Reason} ->
6084 	    e("expect_codec -> encode failed unexpectedly: "
6085	      "~n   Reason: ~w", [Reason]),
6086	    exit({unexpected_encode_result, Reason});
6087	{ok, Bin} when Expect == error ->
6088 	    e("expect_codec -> encode succeded unexpectedly: "
6089	      "~n   ~w", [binary_to_list(Bin)]),
6090	    exit({unexpected_encode_result, binary_to_list(Bin)});
6091	{ok, Bin} ->
6092	    d("expect_codec -> successfull encode as expected:"
6093	      "~n~s", [binary_to_list(Bin)]),
6094	    case (catch decode_message(Codec, false, Conf, Bin)) of
6095		{ok, Msg} ->
6096 		    d("expect_codec -> successfull decode~n", []),
6097		    ok;
6098		{ok, Msg2} ->
6099 		    e("expect_codec -> successfull decode"
6100		      " - but not equal", []),
6101		    chk_MegacoMessage(Msg, Msg2);
6102		%% exit({unexpected_decode_result, Msg, Msg2});
6103		Else ->
6104 		    e("expect_codec -> decode failed:~n~p", [Else]),
6105		    exit({unexpected_decode_result, Else})
6106	    end;
6107	Else ->
6108	    e("expect_codec -> encode failed:~n~p", [Else]),
6109	    exit({unexpected_encode_result, Else})
6110    end.
6111
6112
6113%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
6114
6115msgs() ->
6116    Msgs = msgs1() ++ msgs2() ++ msgs3() ++ msgs4(),
6117    [M || {_, M, _, _} <- Msgs].
6118
6119msgs1() ->
6120    Plain =
6121	fun(Codec, DD, Ver, EC, M) ->
6122		megaco_codec_test_lib:plain_encode_decode(Codec, DD, Ver,
6123							  EC, M)
6124	end,
6125    [
6126     {msg01a, msg1a(),  Plain, [{dbg,false}]},
6127     {msg01b, msg1b(),  Plain, [{dbg,false}]},
6128     {msg02,  msg2(),   Plain, [{dbg,false}]},
6129     {msg03,  msg3(),   Plain, [{dbg,false}]},
6130     {msg04,  msg4(),   Plain, [{dbg,false}]},
6131     {msg05,  msg5(),   Plain, [{dbg,false}]},
6132     {msg06a, msg6a(),  Plain, [{dbg,false}]},
6133     {msg06b, msg6b(),  Plain, [{dbg,false}]},
6134     {msg07,  msg7(),   Plain, [{dbg,false}]},
6135     {msg08a, msg8a(),  Plain, [{dbg,false}]},
6136     {msg08b, msg8b(),  Plain, [{dbg,false}]},
6137     {msg09,  msg9(),   Plain, [{dbg,false}]},
6138     {msg10,  msg10(),  Plain, [{dbg,false}]},
6139     {msg11,  msg11(),  Plain, [{dbg,false}]},
6140     {msg12,  msg12(),  Plain, [{dbg,false}]},
6141     {msg13,  msg13(),  Plain, [{dbg,false}]},
6142     {msg14,  msg14(),  Plain, [{dbg,false}]},
6143     {msg15,  msg15(),  Plain, [{dbg,false}]},
6144     {msg16,  msg16(),  Plain, [{dbg,false}]},
6145     {msg17,  msg17(),  Plain, [{dbg,false}]},
6146     {msg18,  msg18(),  Plain, [{dbg,false}]},
6147     {msg19,  msg19(),  Plain, [{dbg,false}]},
6148     {msg20,  msg20(),  Plain, [{dbg,false}]},
6149     {msg21,  msg21(),  Plain, [{dbg,false}]},
6150     {msg22a, msg22a(), Plain, [{dbg,false}]},
6151     {msg22b, msg22b(), Plain, [{dbg,false}]},
6152     {msg22c, msg22c(), Plain, [{dbg,false}]},
6153     {msg22d, msg22d(), Plain, [{dbg,false}]},
6154     {msg22e, msg22e(), Plain, [{dbg,false}]},
6155     {msg22f, msg22f(), Plain, [{dbg,false}]},
6156     {msg23a, msg23a(), Plain, [{dbg,false}]},
6157     {msg23b, msg23b(), Plain, [{dbg,false}]},
6158     {msg23c, msg23c(), Plain, [{dbg,false}]},
6159     {msg23d, msg23d(), Plain, [{dbg,false}]},
6160     {msg24,  msg24(),  Plain, [{dbg,false}]},
6161     {msg25,  msg25(),  Plain, [{dbg,false}]},
6162     {msg30a, msg30a(), Plain, [{dbg,false}]},
6163     {msg30b, msg30b(), Plain, [{dbg,false}]},
6164     {msg30c, msg30c(), Plain, [{dbg,false}]},
6165     {msg30d, msg30d(), Plain, [{dbg,false}]}
6166    ].
6167
6168
6169msgs2() ->
6170    TransFirst =
6171	fun(Codec, DD, Ver, EC, M) ->
6172		megaco_codec_test_lib:trans_first_encode_decode(Codec, DD,
6173								Ver, EC, M)
6174	end,
6175    ActionsFirst =
6176	fun(Codec, DD, Ver, EC, M) ->
6177		megaco_codec_test_lib:actions_first_encode_decode(Codec, DD,
6178								  Ver, EC, M)
6179	end,
6180    ActionFirst =
6181	fun(Codec, DD, Ver, EC, M) ->
6182		megaco_codec_test_lib:action_first_encode_decode(Codec, DD,
6183								 Ver, EC, M)
6184	end,
6185    [
6186     {msg01a_tf,  msg1a(),  TransFirst,   [{dbg,false}]},
6187     {msg02_tf,   msg2(),   TransFirst,   [{dbg,false}]},
6188     {msg10_tf,   msg10(),  TransFirst,   [{dbg,false}]},
6189     {msg11_tf,   msg11(),  TransFirst,   [{dbg,false}]},
6190     {msg23d_tf,  msg23d(), TransFirst,   [{dbg,false}]},
6191     {msg30b_tf,  msg30b(), TransFirst,   [{dbg,false}]},
6192     {msg30c_tf,  msg30c(), TransFirst,   [{dbg,false}]},
6193     {msg01a_asf, msg1a(),  ActionsFirst, [{dbg,false}]},
6194     {msg02_asf,  msg2(),   ActionsFirst, [{dbg,false}]},
6195     {msg10_asf,  msg10(),  ActionsFirst, [{dbg,false}]},
6196     {msg23d_asf, msg23d(), ActionsFirst, [{dbg,false}]},
6197     {msg01a_af,  msg1a(),  ActionFirst,  [{dbg,false}]},
6198     {msg02_af,   msg2(),   ActionFirst,  [{dbg,false}]},
6199     {msg10_af,   msg10(),  ActionFirst,  [{dbg,false}]},
6200     {msg23d_af,  msg23d(), ActionFirst,  [{dbg,false}]}
6201    ].
6202
6203
6204msgs3() ->
6205    Plain =
6206	fun(Codec, DD, Ver, EC, M) ->
6207		megaco_codec_test_lib:plain_encode_decode(Codec, DD, Ver,
6208							  EC, M)
6209	end,
6210    [{msgs3_name(Name), rfc3525_decode(M), Plain, [{dbg, false}]} ||
6211	{Name, M} <- rfc3525_msgs()].
6212
6213msgs3_name(N) ->
6214    list_to_atom("rfc3525_" ++ atom_to_list(N)).
6215
6216rfc3525_decode(M) when is_list(M) ->
6217    rfc3525_decode(list_to_binary(M));
6218rfc3525_decode(M) when is_binary(M) ->
6219    case (catch decode_message(megaco_pretty_text_encoder, false, [], M)) of
6220	{ok, Msg} ->
6221	    Msg;
6222	Error ->
6223	    {error, {rfc3525_decode_error, Error}}
6224    end.
6225
6226
6227msgs4() ->
6228    Plain =
6229	fun(Codec, DD, Ver, EC, M) ->
6230		megaco_codec_test_lib:plain_encode_decode(Codec, DD, Ver,
6231							  EC, M)
6232	end,
6233    [
6234     {msg51a, msg51a(), Plain, [{dbg, false}]},
6235     {msg51b, msg51b(), Plain, [{dbg, false}]},
6236     {msg51c, msg51c(), Plain, [{dbg, false}]},
6237     {msg51d, msg51d(), Plain, [{dbg, false}]},
6238     {msg51e, msg51e(), Plain, [{dbg, false}]},
6239     {msg51f, msg51f(), Plain, [{dbg, false}]},
6240     {msg51g, msg51g(), Plain, [{dbg, false}]},
6241     {msg51h, msg51h(), Plain, [{dbg, false}]},
6242     {msg51i, msg51i(), Plain, [{dbg, false}]},
6243     {msg52,  msg52(),  Plain, [{dbg, false}]},
6244     {msg53,  msg53(),  Plain, [{dbg, false}]},
6245     {msg54a, msg54a(), Plain, [{dbg, false}]},
6246     {msg54b, msg54b(), Plain, [{dbg, false}]},
6247     {msg54c, msg54c(), Plain, [{dbg, false}]},
6248     {msg55,  msg55(),  Plain, [{dbg, false}]},
6249     {msg56,  msg56(),  Plain, [{dbg, false}]},
6250     {msg57,  msg57(),  Plain, [{dbg, false}]},
6251     {msg58a, msg58a(), Plain, [{dbg, false}]},
6252     {msg58b, msg58b(), Plain, [{dbg, false}]}
6253    ].
6254
6255
6256msgs5() ->
6257    Plain =
6258	fun(Codec, DD, Ver, EC, M) ->
6259		megaco_codec_test_lib:plain_encode_decode(Codec, DD, Ver,
6260							  EC, M)
6261	end,
6262
6263    PlainEDFail =
6264	fun(Codec, DD, Ver, EC, M) ->
6265		Res =
6266		    megaco_codec_test_lib:plain_encode_decode(Codec, DD, Ver,
6267							      EC, M),
6268		case Res of
6269		    {error, {message_encode_failed, Reason, _M}} ->
6270			case Reason of
6271			    {error, {{deprecated, _}, _}} ->
6272				ok;
6273			    _ ->
6274				Res
6275			end;
6276		    _ ->
6277			Res
6278		end
6279	end,
6280
6281    PlainDE =
6282	fun(Codec, _DD, Ver, EC, B) ->
6283		Res =
6284		    megaco_codec_test_lib:decode_message(Codec, false, Ver,
6285							 EC, B),
6286		case Res of
6287		    {ok, M} ->
6288			#'MegacoMessage'{mess = Mess} = M,
6289			#'Message'{messageBody = {transactions, TRs}} = Mess,
6290			[{transactionRequest, TR}] = TRs,
6291			#'TransactionRequest'{actions = Actions} = TR,
6292			[Action] = Actions,
6293			#'ActionRequest'{commandRequests = CmdReqs} = Action,
6294			[CmdReq] = CmdReqs,
6295			#'CommandRequest'{command = Cmd} = CmdReq,
6296			{addReq,AmmReq} = Cmd,
6297			#'AmmRequest'{descriptors = []} = AmmReq,
6298			ok;
6299		    _ ->
6300			Res
6301		end
6302	end,
6303
6304    [
6305     {msg61a, msg61a(), Plain,       [{dbg, false}]},
6306     {msg61b, msg61b(), Plain,       [{dbg, false}]},
6307     {msg61c, msg61c(), Plain,       [{dbg, false}]},
6308     {msg62a, msg62a(), PlainEDFail, [{dbg, false}]},
6309     {msg62b, msg62b(), PlainDE,     [{dbg, false}]}
6310    ].
6311
6312
6313%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
6314
6315msg_actions([], Actions) ->
6316    lists:reverse(Actions);
6317msg_actions([{CtxId, CmdReqs}|ActionInfo], Actions) ->
6318    Action = ?MSG_LIB:cre_ActionRequest(CtxId,CmdReqs),
6319    msg_actions(ActionInfo, [Action|Actions]).
6320
6321megaco_trans_req([], Transactions) ->
6322    {transactions, lists:reverse(Transactions)};
6323megaco_trans_req([{TransId, ActionInfo}|TransInfo], Transactions) ->
6324    Actions = msg_actions(ActionInfo, []),
6325    TR      = ?MSG_LIB:cre_TransactionRequest(TransId, Actions),
6326    Trans   = ?MSG_LIB:cre_Transaction(TR),
6327    megaco_trans_req(TransInfo, [Trans|Transactions]).
6328
6329megaco_message(Version, Mid, Body) ->
6330    Mess = ?MSG_LIB:cre_Message(Version, Mid, Body),
6331    ?MSG_LIB:cre_MegacoMessage(Mess).
6332
6333msg_request(Mid, TransInfo) ->
6334    TransReq = megaco_trans_req(TransInfo, []),
6335    megaco_message(?VERSION, Mid, TransReq).
6336
6337msg_request(Mid, TransId, ContextId, CmdReq) ->
6338    Action  = ?MSG_LIB:cre_ActionRequest(ContextId, CmdReq),
6339    Actions = [Action],
6340    TR      = ?MSG_LIB:cre_TransactionRequest(TransId, Actions),
6341    Trans   = ?MSG_LIB:cre_Transaction(TR),
6342    Mess    = ?MSG_LIB:cre_Message(?VERSION, Mid, [Trans]),
6343    ?MSG_LIB:cre_MegacoMessage(Mess).
6344
6345msg_request(Auth, Mid, TransId, ContextId, CmdReq) ->
6346    Action  = ?MSG_LIB:cre_ActionRequest(ContextId, CmdReq),
6347    Actions = [Action],
6348    TR      = ?MSG_LIB:cre_TransactionRequest(TransId, Actions),
6349    Trans   = ?MSG_LIB:cre_Transaction(TR),
6350    Mess    = ?MSG_LIB:cre_Message(?VERSION, Mid, [Trans]),
6351    ?MSG_LIB:cre_MegacoMessage(Auth, Mess).
6352
6353msg_reply(Mid, TransId, ContextId, CmdReply) ->
6354    Action  = cre_ActRep(ContextId, CmdReply),
6355    Actions = [Action],
6356    TR      = cre_TransRep(TransId, Actions),
6357    Trans   = ?MSG_LIB:cre_Transaction(TR),
6358    Mess    = ?MSG_LIB:cre_Message(?VERSION, Mid, [Trans]),
6359    ?MSG_LIB:cre_MegacoMessage(Mess).
6360
6361msg_ack(Mid, [Range|_] = Ranges) when is_tuple(Range) ->
6362    msg_ack(Mid, [Ranges]);
6363
6364msg_ack(Mid, Ranges) ->
6365    %% TRAs = make_tras(Ranges, []),
6366    TRAs = make_tras(Ranges),
6367    Req  = {transactions, TRAs},
6368    cre_MegacoMessage(?VERSION, Mid, Req).
6369
6370make_tras(TRARanges) ->
6371    F = fun(R) -> {transactionResponseAck, make_tra(R)} end,
6372    lists:map(F, TRARanges).
6373
6374make_tra(Ranges) ->
6375    F = fun({F,L}) -> cre_TransAck(F,L) end,
6376    lists:map(F, Ranges).
6377
6378
6379%% -------------------------------------------------------------------------
6380
6381
6382msg1(Mid, Tid) ->
6383    Gain  = cre_PropParm("tdmc/gain", "2"),
6384    Ec    = cre_PropParm("tdmc/ec", "g165"),
6385    LCD   = cre_LocalControlDesc(sendRecv,[Gain, Ec]),
6386    V     = cre_PropParm("v", "0"),
6387    %% C    = cre_PropParm("c", "IN IP4 $ "),
6388    C     = cre_PropParm("c", [$I,$N,$ ,$I,$P,$4,$ ,$$,$ ]),
6389    M     = cre_PropParm("m", "audio $ RTP/AVP 0"),
6390    A     = cre_PropParm("a", "fmtp:PCMU VAD=X-NNVAD"),
6391    LD    = cre_LocalRemoteDesc([[V, C, M, A]]),
6392    Parms = cre_StreamParms(LCD,LD),
6393    StreamDesc = cre_StreamDesc(1,Parms),
6394    MediaDesc  = cre_MediaDesc(StreamDesc),
6395    ReqEvent   = cre_ReqedEv("al/of"),
6396    EventsDesc = cre_EvsDesc(2222,[ReqEvent]),
6397    AmmReq     = cre_AmmReq([#megaco_term_id{id = Tid}],
6398			    [{mediaDescriptor, MediaDesc},
6399			     {eventsDescriptor, EventsDesc}]),
6400    CmdReq     = cre_CmdReq({modReq, AmmReq}),
6401    msg_request(Mid, 9999, ?megaco_null_context_id, [CmdReq]).
6402
6403msg1a() ->
6404    msg1a(?MGC_MID).
6405msg1a(Mid) ->
6406    msg1(Mid, ?A4444).
6407
6408msg1b() ->
6409    msg1b(?MGC_MID).
6410msg1b(Mid) ->
6411    msg1(Mid, ?A4445).
6412
6413
6414%% --------------------------
6415
6416
6417msg2() ->
6418    msg2(?MGC_MID).
6419msg2(Mid) ->
6420    msg2(Mid, ?A4444).
6421msg2(Mid, Tid) ->
6422    Gain  = cre_PropParm("tdmc/gain", "2"),
6423    Ec    = cre_PropParm("tdmc/ec", "g165"),
6424    LCD   = cre_LocalControlDesc(sendRecv,[Gain, Ec]),
6425    V     = cre_PropParm("v", "0"),
6426    %% C    = cre_PropParm("c", "IN IP4 $ "),
6427    C     = cre_PropParm("c", [$I,$N,$ ,$I,$P,$4,$ ,$$,$ ]),
6428    M     = cre_PropParm("m", "audio $ RTP/AVP 0"),
6429    A     = cre_PropParm("a", "fmtp:PCMU VAD=X-NNVAD"),
6430    LD    = cre_LocalRemoteDesc([[V, C, M, A]]),
6431    Parms = cre_StreamParms(LCD,LD),
6432    StreamDesc = cre_StreamDesc(1,Parms),
6433    MediaDesc  = cre_MediaDesc(StreamDesc),
6434    EventParm  = cre_EvParm("strict",["exact"]),
6435    ReqEvent   = cre_ReqedEv("al/of", [EventParm]),
6436    EventsDesc = cre_EvsDesc(2222,[ReqEvent]),
6437    AmmReq     = cre_AmmReq([#megaco_term_id{id = Tid}],
6438			    [{mediaDescriptor, MediaDesc},
6439			     {eventsDescriptor, EventsDesc}]),
6440    CmdReq     = cre_CmdReq({modReq, AmmReq}),
6441    msg_request(Mid, 9999, ?megaco_null_context_id, [CmdReq]).
6442
6443
6444%% --------------------------
6445
6446msg3() ->
6447    msg3(?MG1_MID).
6448msg3(Mid) ->
6449    TimeStamp = cre_TimeNot("19990729", "22000000"),
6450    Event     = cre_ObsEv("al/of",TimeStamp),
6451    Desc      = cre_ObsEvsDesc(2222,[Event]),
6452    NotifyReq = cre_NotifyReq([#megaco_term_id{id = ?A4444}],Desc),
6453    CmdReq    = cre_CmdReq({notifyReq, NotifyReq}),
6454    msg_request(Mid, 10000, ?megaco_null_context_id, [CmdReq]).
6455
6456
6457%% --------------------------
6458
6459msg4() ->
6460    msg4(?MG1_MID_NO_PORT, "901 mg col boot").
6461msg4(Mid, Reason) when is_list(Reason) ->
6462    Address = {portNumber, ?DEFAULT_PORT},
6463    Profile = cre_SvcChProf("resgw",1),
6464    Parm    = cre_SvcChParm(restart,Address,[Reason],Profile),
6465    Req     = cre_SvcChReq([?megaco_root_termination_id],Parm),
6466    CmdReq  = cre_CmdReq({serviceChangeReq, Req}),
6467    msg_request(Mid, 9998, ?megaco_null_context_id, [CmdReq]).
6468
6469
6470%% --------------------------
6471
6472msg5() ->
6473    msg5(?MGC_MID).
6474msg5(Mid) ->
6475    Address = {portNumber, ?DEFAULT_PORT},
6476    Profile = cre_SvcChProf("resgw",1),
6477    Parm    = cre_SvcChResParm(Address,Profile),
6478    Reply   = cre_SvcChRep([?megaco_root_termination_id],
6479			   {serviceChangeResParms,Parm}),
6480    msg_reply(Mid, 9998, ?megaco_null_context_id,
6481	      [{serviceChangeReply, Reply}]).
6482
6483
6484%% --------------------------
6485
6486msg6(Mid, Tid) ->
6487    Reply = cre_AmmsReply([#megaco_term_id{id = Tid}]),
6488    msg_reply(Mid, 9999, ?megaco_null_context_id, [{modReply, Reply}]).
6489
6490msg6a() ->
6491    msg6a(?MG1_MID).
6492msg6a(Mid) ->
6493    msg6(Mid, ?A4444).
6494
6495msg6b() ->
6496    msg6b(?MG2_MID).
6497msg6b(Mid) ->
6498    msg6(Mid, ?A5555).
6499
6500
6501%% --------------------------
6502
6503msg7() ->
6504    msg7(?MGC_MID).
6505msg7(Mid) ->
6506    Reply = cre_NotifyRep([#megaco_term_id{id = ?A4444}]),
6507    msg_reply(Mid, 10000, ?megaco_null_context_id, [{notifyReply, Reply}]).
6508
6509
6510%% --------------------------
6511
6512msg8(Mid, DigitMapValue) ->
6513    Strict = cre_EvParm("strict",["state"]),
6514    On     = cre_ReqedEv("al/on", [Strict]),
6515    Name   = "dialplan00",
6516    Action = cre_ReqedActs(Name),
6517    Ce     = cre_ReqedEv("dd/ce", Action),
6518    EventsDesc = cre_EvsDesc(2223,[On, Ce]),
6519    Signal     = cre_Sig("cg/rt"),
6520    DigMapDesc = cre_DigitMapDesc(Name, DigitMapValue),
6521    AmmReq     = cre_AmmReq([#megaco_term_id{id = ?A4444}],
6522                           [{eventsDescriptor, EventsDesc},
6523			    {signalsDescriptor, [{signal, Signal}]},
6524			    {digitMapDescriptor, DigMapDesc}]),
6525    CmdReq     = cre_CmdReq({modReq, AmmReq}),
6526    msg_request(Mid, 10001, ?megaco_null_context_id, [CmdReq]).
6527
6528msg8a() ->
6529    msg8a(?MGC_MID).
6530msg8a(Mid) ->
6531    Body = "(0s| 00s|[1-7]xlxx|8lxxxxxxx|#xxxxxxx|*xx|9l1xxxxxxxxxx|9l011x.s)",
6532    Value = cre_DigitMapValue(Body),
6533    msg8(Mid, Value).
6534
6535msg8b() ->
6536    msg8b(?MGC_MID).
6537msg8b(Mid) ->
6538    Body = "(0s| 00s|[1-7]xlxx|8lxxxxxxx|#xxxxxxx|*xx|9l1xxxxxxxxxx|9l011x.s)",
6539    Value = cre_DigitMapValue(Body, 1, 23, 99),
6540    msg8(Mid, Value).
6541
6542
6543%% --------------------------
6544
6545msg9() ->
6546    msg9(?MG1_MID).
6547msg9(Mid) ->
6548    TimeStamp = cre_TimeNot("19990729","22010001"),
6549    Parm      = cre_EvParm("ds",["916135551212"]),
6550    Event     = cre_ObsEv("dd/ce",TimeStamp,[Parm]),
6551    Desc      = cre_ObsEvsDesc(2223,[Event]),
6552    NotifyReq = cre_NotifyReq([#megaco_term_id{id = ?A4444}], Desc),
6553    CmdReq    = cre_CmdReq({notifyReq, NotifyReq}),
6554    msg_request(Mid, 10002, ?megaco_null_context_id, [CmdReq]).
6555
6556
6557%% --------------------------
6558
6559msg10() ->
6560    msg10(?MGC_MID).
6561msg10(Mid) ->
6562    AmmReq = cre_AmmReq([#megaco_term_id{id = ?A4444}],[]),
6563    CmdReq = cre_CmdReq({addReq, AmmReq}),
6564    Jit = cre_PropParm("nt/jit", "40"),
6565    LCD = cre_LocalControlDesc(recvOnly,[Jit]),
6566    V   = cre_PropParm("v", "0"),
6567    C   = cre_PropParm("c", "IN IP4 $ "),
6568    M   = cre_PropParm("m", "audio $ RTP/AVP 4"),
6569    A   = cre_PropParm("a", "ptime:30"),
6570    V2  = cre_PropParm("v", "0"),
6571    C2  = cre_PropParm("c", "IN IP4 $ "),
6572    M2  = cre_PropParm("m", "audio $ RTP/AVP 0"),
6573    LD  = cre_LocalRemoteDesc([[V, C, M, A], [V2, C2, M2]]),
6574    Parms      = cre_StreamParms(LCD, LD),
6575    StreamDesc = cre_StreamDesc(1,Parms),
6576    MediaDesc  = cre_MediaDesc(StreamDesc),
6577    ChooseTid  = #megaco_term_id{contains_wildcards = true,
6578				 id = [[?megaco_choose]]},
6579    AmmReq2    = cre_AmmReq([ChooseTid],[{mediaDescriptor, MediaDesc}]),
6580    CmdReq2    = cre_CmdReq({addReq, AmmReq2}),
6581    msg_request(Mid, 10003, ?megaco_choose_context_id, [CmdReq, CmdReq2]).
6582
6583
6584msg11() ->
6585    msg11(?MG1_MID).
6586msg11(Mid) ->
6587    V  = cre_PropParm("v", "0"),
6588    C  = cre_PropParm("c", "IN IP4 124.124.124.222"),
6589    M  = cre_PropParm("m", "audio 2222 RTP/AVP 4"),
6590    A  = cre_PropParm("a", "ptime:30"),
6591    A2 = cre_PropParm("a", "recvonly"),
6592    LD = cre_LocalRemoteDesc([[V, C, M, A, A2]]),
6593    Parms      = cre_StreamParmsL(LD),
6594    StreamDesc = cre_StreamDesc(1, Parms),
6595    MediaDesc  = cre_MediaDesc(StreamDesc),
6596    Reply  = cre_AmmsReply([#megaco_term_id{id = ?A4444}]),
6597    Reply2 = cre_AmmsReply([#megaco_term_id{id = ?A4445}],
6598			   [{mediaDescriptor, MediaDesc}]),
6599    msg_reply(Mid, 10003, 2000, [{addReply, Reply}, {addReply, Reply2}]).
6600
6601
6602%% --------------------------
6603
6604msg12() ->
6605    msg12(?MGC_MID).
6606msg12(Mid) ->
6607    LCD        = cre_LocalControlDesc(sendRecv),
6608    Parms      = cre_StreamParms(LCD),
6609    StreamDesc = cre_StreamDesc(1,Parms),
6610    MediaDesc  = cre_MediaDesc(StreamDesc),
6611    Signal     = cre_Sig("al/ri"),
6612    Descs      = [{mediaDescriptor, MediaDesc},
6613		  {signalsDescriptor, [{signal, Signal}]}],
6614    AmmReq     = cre_AmmReq([#megaco_term_id{id = ?A5555}], Descs),
6615    CmdReq     = cre_CmdReq({addReq, AmmReq}),
6616    Jit        = cre_PropParm("nt/jit", "40"),
6617    LCD2       = cre_LocalControlDesc(sendRecv, [Jit]),
6618    V      = cre_PropParm("v", "0"),
6619    C      = cre_PropParm("c", "IN IP4 $ "),
6620    M      = cre_PropParm("m", "audio $ RTP/AVP 4"),
6621    A      = cre_PropParm("a", "ptime:30"),
6622    LD2    = cre_LocalRemoteDesc([[V, C, M, A]]),
6623    V2     = cre_PropParm("v", "0"),
6624    C2     = cre_PropParm("c", "IN IP4 124.124.124.222"),
6625    M2     = cre_PropParm("m", "audio 2222 RTP/AVP 4"),
6626    RD2    = cre_LocalRemoteDesc([[V2, C2, M2]]),
6627    Parms2 = cre_StreamParms(LCD2,LD2,RD2),
6628    StreamDesc2 = cre_StreamDesc(1,Parms2),
6629    MediaDesc2  = cre_MediaDesc(StreamDesc2),
6630    ChooseTid   = #megaco_term_id{contains_wildcards = true,
6631				  id = [[?megaco_choose]]},
6632    AmmReq2     = cre_AmmReq([ChooseTid],[{mediaDescriptor, MediaDesc2}]),
6633    CmdReq2     = cre_CmdReq({addReq, AmmReq2}),
6634    msg_request(Mid, 50003, ?megaco_choose_context_id, [CmdReq, CmdReq2]).
6635
6636
6637%% --------------------------
6638
6639msg13() ->
6640    msg13(?MG2_MID).
6641msg13(Mid) ->
6642    V     = cre_PropParm("v", "0"),
6643    C     = cre_PropParm("c", "IN IP4 125.125.125.111"),
6644    M     = cre_PropParm("m", "audio 1111 RTP/AVP 4"),
6645    LD    = cre_LocalRemoteDesc([[V, C, M]]),
6646    Parms = cre_StreamParmsL(LD),
6647    StreamDesc = cre_StreamDesc(1,Parms),
6648    MediaDesc  = cre_MediaDesc(StreamDesc),
6649    Reply      = cre_AmmsReply([#megaco_term_id{id = ?A5556}],
6650			       [{mediaDescriptor, MediaDesc}]),
6651    msg_reply(Mid, 50003, 5000, [{addReply, Reply}]).
6652
6653
6654%% --------------------------
6655
6656msg14() ->
6657    msg14(?MGC_MID).
6658msg14(Mid) ->
6659    %% Cmd 1)
6660    Signal      = cre_Sig("cg/rt"),
6661    AmmReq1     = cre_AmmReq([#megaco_term_id{id = ?A4444}],
6662			     [{signalsDescriptor, [{signal, Signal}]}]),
6663    CmdReq1     = cre_CmdReq({modReq, AmmReq1}),
6664
6665    %% Cmd 2)
6666    Gain        = cre_PropParm("tdmc/gain", "2"),
6667    Ec          = cre_PropParm("tdmc/ec", "g165"),
6668    LCD         = cre_LocalControlDesc(sendRecv, [Gain, Ec]),
6669    Parms2      = cre_StreamParms(LCD),
6670    StreamDesc2 = cre_StreamDesc(1,Parms2),
6671    MediaDesc2  = cre_MediaDesc(StreamDesc2),
6672    AmmReq2     = cre_AmmReq([#megaco_term_id{id = ?A4445}],
6673			     [{mediaDescriptor, MediaDesc2}]),
6674    CmdReq2     = cre_CmdReq({modReq, AmmReq2}),
6675
6676    %% Cmd 3)
6677    V           = cre_PropParm("v", "0"),
6678    C           = cre_PropParm("c", "IN IP4 125.125.125.111"),
6679    M           = cre_PropParm("m", "audio 1111 RTP/AVP 4"),
6680    RD          = cre_LocalRemoteDesc([[V, C, M]]),
6681    Parms3      = cre_StreamParmsR(RD),
6682    StreamDesc3 = cre_StreamDesc(2,Parms3),
6683    MediaDesc3  = cre_MediaDesc(StreamDesc3),
6684    AmmReq3     = cre_AmmReq([#megaco_term_id{id = ?A4445}],
6685			     [{mediaDescriptor, MediaDesc3}]),
6686    CmdReq3     = cre_CmdReq({modReq, AmmReq3}),
6687    msg_request(Mid, 10005, 2000, [CmdReq1, CmdReq2, CmdReq3]).
6688
6689
6690%% --------------------------
6691
6692msg15() ->
6693    msg15(?MG1_MID).
6694msg15(Mid) ->
6695    Reply  = cre_AmmsReply([#megaco_term_id{id = ?A4444}]),
6696    Reply2 = cre_AmmsReply([#megaco_term_id{id = ?A4445}]),
6697    msg_reply(Mid, 10005, 2000, [{modReply, Reply}, {modReply, Reply2}]).
6698
6699
6700%% --------------------------
6701
6702msg16() ->
6703    msg16(?MG2_MID).
6704msg16(Mid) ->
6705    TimeStamp = cre_TimeNot("19990729","22020002"),
6706    Event     = cre_ObsEv("al/of",TimeStamp),
6707    Desc      = cre_ObsEvsDesc(1234,[Event]),
6708    NotifyReq = cre_NotifyReq([#megaco_term_id{id = ?A5555}],Desc),
6709    CmdReq    = cre_CmdReq({notifyReq, NotifyReq}),
6710    msg_request(Mid, 50005, 5000, [CmdReq]).
6711
6712
6713%% --------------------------
6714
6715msg17() ->
6716    msg17(?MGC_MID).
6717msg17(Mid) ->
6718    Reply = cre_NotifyRep([#megaco_term_id{id = ?A5555}]),
6719    msg_reply(Mid, 50005, ?megaco_null_context_id, [{notifyReply, Reply}]).
6720
6721
6722%% --------------------------
6723
6724msg18() ->
6725    msg18(?MGC_MID).
6726msg18(Mid) ->
6727    On         = cre_ReqedEv("al/on"),
6728    EventsDesc = cre_EvsDesc(1235,[On]),
6729    AmmReq     = cre_AmmReq([#megaco_term_id{id = ?A5555}],
6730			    [{eventsDescriptor, EventsDesc},
6731			     {signalsDescriptor, []}]),
6732    CmdReq     = cre_CmdReq({modReq, AmmReq}),
6733    msg_request(Mid, 50006, 5000, [CmdReq]).
6734
6735
6736%% --------------------------
6737
6738msg19() ->
6739    msg19(?MG2_MID).
6740msg19(Mid) ->
6741    Reply = cre_AmmsReply([#megaco_term_id{id = ?A4445}]),
6742    msg_reply(Mid, 50006, 5000, [{modReply, Reply}]).
6743
6744
6745%% --------------------------
6746
6747msg20() ->
6748    msg20(?MGC_MID).
6749msg20(Mid) ->
6750    LCD        = cre_LocalControlDesc(sendRecv),
6751    Parms      = cre_StreamParms(LCD),
6752    StreamDesc = cre_StreamDesc(1,Parms),
6753    MediaDesc  = cre_MediaDesc(StreamDesc),
6754    AmmReq     = cre_AmmReq([#megaco_term_id{id = ?A4445}],
6755			    [{mediaDescriptor, MediaDesc}]),
6756    CmdReq     = cre_CmdReq({modReq, AmmReq}),
6757    AmmReq2    = cre_AmmReq([#megaco_term_id{id = ?A4444}],
6758                            [{signalsDescriptor, []}]),
6759    CmdReq2    = cre_CmdReq({modReq, AmmReq2}),
6760    msg_request(Mid, 10006, 2000, [CmdReq, CmdReq2]).
6761
6762
6763%% --------------------------
6764
6765msg21() ->
6766    msg21(?MGC_MID).
6767msg21(Mid) ->
6768    Tokens    = [mediaToken, eventsToken, signalsToken,
6769		 digitMapToken, statsToken, packagesToken],
6770    AuditDesc = cre_AuditDesc(Tokens),
6771    Req       = cre_AuditReq(#megaco_term_id{id = ?A5556},AuditDesc),
6772    CmdReq    = cre_CmdReq({auditValueRequest, Req}),
6773    msg_request(Mid, 50007, ?megaco_null_context_id, [CmdReq]).
6774
6775
6776%% --------------------------
6777
6778msg22a() ->
6779    msg22(1).
6780
6781msg22b() ->
6782    msg22(10).
6783
6784msg22c() ->
6785    msg22(25).
6786
6787msg22d() ->
6788    msg22(50).
6789
6790msg22e() ->
6791    msg22(75).
6792
6793msg22f() ->
6794    msg22(100).
6795
6796msg22(N) ->
6797    msg22(?MG2_MID, N).
6798msg22(Mid, N) ->
6799    Jit = cre_PropParm("nt/jit", "40"),
6800    LCD = cre_LocalControlDesc(sendRecv,[Jit]),
6801    LDV = cre_PropParm("v", "0"),
6802    LDC = cre_PropParm("c", "IN IP4 125.125.125.111"),
6803    LDM = cre_PropParm("m", "audio 1111 RTP/AVP  4"),
6804    LDA = cre_PropParm("a", "ptime:30"),
6805    LD  = cre_LocalRemoteDesc([[LDV, LDC, LDM, LDA]]),
6806    RDV = cre_PropParm("v", "0"),
6807    RDC = cre_PropParm("c", "IN IP4 124.124.124.222"),
6808    RDM = cre_PropParm("m", "audio 2222 RTP/AVP  4"),
6809    RDA = cre_PropParm("a", "ptime:30"),
6810    RD  = cre_LocalRemoteDesc([[RDV, RDC, RDM, RDA]]),
6811    StreamParms   = cre_StreamParms(LCD,LD,RD),
6812    StreamDesc    = cre_StreamDesc(1,StreamParms),
6813    Media         = cre_MediaDesc(StreamDesc),
6814    PackagesItem  = cre_PkgsItem("nt",1),
6815    PackagesItem2 = cre_PkgsItem("rtp",1),
6816    Stat       = cre_StatsParm("rtp/ps","1200"),
6817    Stat2      = cre_StatsParm("nt/os","62300"),
6818    Stat3      = cre_StatsParm("rtp/pr","700"),
6819    Stat4      = cre_StatsParm("nt/or","45100"),
6820    Stat5      = cre_StatsParm("rtp/pl","0.2"),
6821    Stat6      = cre_StatsParm("rtp/jit","20"),
6822    Stat7      = cre_StatsParm("rtp/delay","40"),
6823    Statistics = [Stat, Stat2, Stat3, Stat4, Stat5, Stat6, Stat7],
6824    Audits     = [{mediaDescriptor, Media},
6825		  {packagesDescriptor, [PackagesItem, PackagesItem2]},
6826		  {statisticsDescriptor, Statistics}],
6827    Reply      = {auditResult,
6828		  cre_AuditRes(#megaco_term_id{id = ?A5556},Audits)},
6829    msg_reply(Mid, 50007, ?megaco_null_context_id,
6830	      lists:duplicate(N,{auditValueReply, Reply})).
6831%%     msg_reply(Mid, 50007, ?megaco_null_context_id,
6832%% 	      lists.duplicate([{auditValueReply, Reply}]).
6833
6834
6835%% --------------------------
6836
6837msg23a() ->
6838    msg23a(?MG2_MID).
6839msg23a(Mid) ->
6840    TimeStamp = cre_TimeNot("19990729","24020002"),
6841    Event     = cre_ObsEv("al/on",TimeStamp),
6842    Desc      = cre_ObsEvsDesc(1235,[Event]),
6843    NotifyReq = cre_NotifyReq([#megaco_term_id{id = ?A5555}],Desc),
6844    CmdReq    = cre_CmdReq({notifyReq, NotifyReq}),
6845    msg_request(Mid, 50008, 5000, [CmdReq]).
6846
6847
6848msg23b() ->
6849    msg23b(?MG2_MID).
6850msg23b(Mid) ->
6851    TimeStamp  = cre_TimeNot("19990729","24020002"),
6852    Event      = cre_ObsEv("al/on",TimeStamp),
6853    Desc       = cre_ObsEvsDesc(1235,[Event]),
6854    NotifyReq1 = cre_NotifyReq([#megaco_term_id{id = ?A5555}],Desc),
6855    CmdReq1    = cre_CmdReq({notifyReq, NotifyReq1}),
6856    NotifyReq2 = cre_NotifyReq([#megaco_term_id{id = ?A5556}],Desc),
6857    CmdReq2    = cre_CmdReq({notifyReq, NotifyReq2}),
6858    ActionInfo = [{5000, [CmdReq1]}, {5001, [CmdReq2]}],
6859    TransInfo  = [{50008, ActionInfo}],
6860    msg_request(Mid, TransInfo).
6861
6862
6863msg23c() ->
6864    msg23c(?MG2_MID).
6865msg23c(Mid) ->
6866    TimeStamp  = cre_TimeNot("19990729","24020002"),
6867    Event      = cre_ObsEv("al/on",TimeStamp),
6868    Desc       = cre_ObsEvsDesc(1235,[Event]),
6869    NotifyReq1 = cre_NotifyReq([#megaco_term_id{id = ?A5555}],Desc),
6870    CmdReq1    = cre_CmdReq({notifyReq, NotifyReq1}),
6871    NotifyReq2 = cre_NotifyReq([#megaco_term_id{id = ?A5556}],Desc),
6872    CmdReq2    = cre_CmdReq({notifyReq, NotifyReq2}),
6873    ActionInfo1 = [{5000, [CmdReq1]}],
6874    ActionInfo2 = [{5001, [CmdReq2]}],
6875    TransInfo   = [{50008, ActionInfo1}, {50009, ActionInfo2}],
6876    msg_request(Mid, TransInfo).
6877
6878
6879msg23d() ->
6880    msg23d(?MG2_MID).
6881msg23d(Mid) ->
6882    TimeStamp  = cre_TimeNot("19990729","24020002"),
6883    Event      = cre_ObsEv("al/on",TimeStamp),
6884    Desc       = cre_ObsEvsDesc(1235,[Event]),
6885    NotifyReq1 = cre_NotifyReq([#megaco_term_id{id = ?A5555}],Desc),
6886    CmdReq1    = cre_CmdReq({notifyReq, NotifyReq1}),
6887    NotifyReq2 = cre_NotifyReq([#megaco_term_id{id = ?A5556}],Desc),
6888    CmdReq2    = cre_CmdReq({notifyReq, NotifyReq2}),
6889    NotifyReq3 = cre_NotifyReq([#megaco_term_id{id = ?A4444}],Desc),
6890    CmdReq3    = cre_CmdReq({notifyReq, NotifyReq3}),
6891    NotifyReq4 = cre_NotifyReq([#megaco_term_id{id = ?A4445}],Desc),
6892    CmdReq4    = cre_CmdReq({notifyReq, NotifyReq4}),
6893    ActionInfo1 = [{5000, [CmdReq1]}, {5001, [CmdReq2]}],
6894    ActionInfo2 = [{5003, [CmdReq3]}, {5004, [CmdReq4]}],
6895    TransInfo   = [{50008, ActionInfo1}, {50009, ActionInfo2}],
6896    msg_request(Mid, TransInfo).
6897
6898
6899%% --------------------------
6900
6901msg24() ->
6902    msg24(?MGC_MID).
6903msg24(Mid) ->
6904    AuditDesc = cre_AuditDesc([statsToken]),
6905    SubReq    = cre_SubReq([#megaco_term_id{id = ?A5555}], AuditDesc),
6906    SubReq2   = cre_SubReq([#megaco_term_id{id = ?A5556}], AuditDesc),
6907    CmdReq    = cre_CmdReq({subtractReq, SubReq}),
6908    CmdReq2   = cre_CmdReq({subtractReq, SubReq2}),
6909    msg_request(Mid, 50009, 5000, [CmdReq, CmdReq2]).
6910
6911
6912%% --------------------------
6913
6914msg25() ->
6915    msg25(?MG2_MID).
6916msg25(Mid) ->
6917    Stat11 = cre_StatsParm("nt/os","45123"),
6918    Stat12 = cre_StatsParm("nt/dur", "40"),
6919    Stats1 = [Stat11, Stat12],
6920    Reply1 = cre_AmmsReply([#megaco_term_id{id = ?A5555}],
6921			   [{statisticsDescriptor, Stats1}]),
6922    Stat21 = cre_StatsParm("rtp/ps","1245"),
6923    Stat22 = cre_StatsParm("nt/os", "62345"),
6924    Stat23 = cre_StatsParm("rtp/pr", "780"),
6925    Stat24 = cre_StatsParm("nt/or", "45123"),
6926    Stat25 = cre_StatsParm("rtp/pl", "10"),
6927    Stat26 = cre_StatsParm("rtp/jit", "27"),
6928    Stat27 = cre_StatsParm("rtp/delay","48"),
6929    Stats2 = [Stat21, Stat22, Stat23, Stat24, Stat25, Stat26, Stat27],
6930    Reply2 = cre_AmmsReply([#megaco_term_id{id = ?A5556}],
6931                          [{statisticsDescriptor, Stats2}]),
6932    msg_reply(Mid, 50009, 5000,
6933	      [{subtractReply, Reply1}, {subtractReply, Reply2}]).
6934
6935
6936msg30a() ->
6937    msg_ack(?MG2_MID, [{9,9}]).
6938
6939msg30b() ->
6940    msg_ack(?MG2_MID, [{9,13}]).
6941
6942msg30c() ->
6943    msg_ack(?MG2_MID,
6944	    [{9,13},   {15,15},  {33,40},  {50,60},  {70,80},  {85,90},
6945	     {101,105},{109,119},{121,130},{140,160},{170,175},{180,189},
6946	     {201,205},{209,219},{221,230},{240,260},{270,275},{280,289},
6947	     {301,305},{309,319},{321,330},{340,360},{370,375},{380,389},
6948	     {401,405},{409,419},{421,430},{440,460},{470,475},{480,489},
6949	     {501,505},{509,519},{521,530},{540,560},{570,575},{580,589}
6950	    ]).
6951
6952%% Don't think this will be used by the megaco stack, but since it
6953%% seem's to be a valid construction...
6954msg30d() ->
6955    msg_ack(?MG2_MID,
6956	    [[{9,13},   {15,15},  {33,40},  {50,60},  {70,80},  {85,90}],
6957	     [{101,105},{109,119},{121,130},{140,160},{170,175},{180,189}],
6958	     [{201,205},{209,219},{221,230},{240,260},{270,275},{280,289}],
6959	     [{301,305},{309,319},{321,330},{340,360},{370,375},{380,389}],
6960	     [{401,405},{409,419},{421,430},{440,460},{470,475},{480,489}],
6961	     [{501,505},{509,519},{521,530},{540,560},{570,575},{580,589}]
6962	    ]).
6963
6964
6965
6966msg40() ->
6967    msg40(?MG1_MID_NO_PORT, "901 mg col boot").
6968msg40(Mid, Reason) when is_list(Reason) ->
6969    Address = {portNumber, ?DEFAULT_PORT},
6970    Profile = cre_SvcChProf("resgw",1),
6971    Parm    = cre_SvcChParm(restart,Address,[Reason],Profile),
6972    Req     = cre_SvcChReq([?megaco_root_termination_id],Parm),
6973    CmdReq  = cre_CmdReq({serviceChangeReq, Req}),
6974    Auth    = cre_AuthHeader(),
6975    msg_request(Auth, Mid, 9998, ?megaco_null_context_id, [CmdReq]).
6976
6977
6978msg50(Mid, APT) ->
6979    AD     = cre_AuditDesc(asn1_NOVALUE, APT),
6980    Req    = cre_AuditReq(#megaco_term_id{id = ?A5556},AD),
6981    CmdReq = cre_CmdReq({auditValueRequest, Req}),
6982    msg_request(Mid, 50007, ?megaco_null_context_id, [CmdReq]).
6983
6984%% IndAudMediaDescriptor:
6985msg51(Mid, IATSDorStream) ->
6986    IAMD   = cre_IndAudMediaDesc(IATSDorStream),
6987    IAP    = cre_IndAudParam(IAMD),
6988    APT    = [IAP],
6989    msg50(Mid, APT).
6990
6991msg51a() ->
6992    msg51a(?MG2_MID).
6993msg51a(Mid) ->
6994    PP    = cre_IndAudPropertyParm("tdmc/gain"),
6995    PPs   = [PP],
6996    IATSD = cre_IndAudTermStateDesc(PPs),
6997    msg51(Mid, IATSD).
6998
6999msg51b() ->
7000    msg51b(?MG2_MID).
7001msg51b(Mid) ->
7002    PP    = cre_IndAudPropertyParm("nt/jit"),
7003    PPs   = [PP],
7004    IATSD = cre_IndAudTermStateDesc(PPs),
7005    msg51(Mid, IATSD).
7006
7007msg51c() ->
7008    msg51c(?MG2_MID).
7009msg51c(Mid) ->
7010    IATSD = cre_IndAudTermStateDesc([], asn1_NOVALUE, 'NULL'),
7011    msg51(Mid, IATSD).
7012
7013msg51d() ->
7014    msg51d(?MG2_MID).
7015msg51d(Mid) ->
7016    IATSD = cre_IndAudTermStateDesc([], 'NULL', asn1_NOVALUE),
7017    msg51(Mid, IATSD).
7018
7019msg51e() ->
7020    msg51e(?MG2_MID).
7021msg51e(Mid) ->
7022    IALCD = cre_IndAudLocalControlDesc('NULL', asn1_NOVALUE,
7023				       asn1_NOVALUE, asn1_NOVALUE),
7024    IASP = cre_IndAudStreamParms(IALCD),
7025    msg51(Mid, IASP).
7026
7027msg51f() ->
7028    msg51f(?MG2_MID).
7029msg51f(Mid) ->
7030    IALCD = cre_IndAudLocalControlDesc(asn1_NOVALUE, 'NULL',
7031				       asn1_NOVALUE, asn1_NOVALUE),
7032    IASP = cre_IndAudStreamParms(IALCD),
7033    msg51(Mid, IASP).
7034
7035msg51g() ->
7036    msg51g(?MG2_MID).
7037msg51g(Mid) ->
7038    IALCD = cre_IndAudLocalControlDesc(asn1_NOVALUE, asn1_NOVALUE,
7039				       'NULL', asn1_NOVALUE),
7040    IASP = cre_IndAudStreamParms(IALCD),
7041    msg51(Mid, IASP).
7042
7043msg51h() ->
7044    msg51h(?MG2_MID).
7045msg51h(Mid) ->
7046    Name  = "nt/jit",
7047    IAPP  = cre_IndAudPropertyParm(Name),
7048    IALCD = cre_IndAudLocalControlDesc(asn1_NOVALUE, asn1_NOVALUE,
7049				       asn1_NOVALUE, [IAPP]),
7050    IASP  = cre_IndAudStreamParms(IALCD),
7051    SID   = 123,
7052    IASD  = cre_IndAudStreamDesc(SID, IASP),
7053    msg51(Mid, [IASD]).
7054
7055
7056msg51i() ->
7057    msg51i(?MG2_MID).
7058msg51i(Mid) ->
7059    Name  = "nt/jit",
7060    Name2 = "tdmc/ec",
7061    IAPP  = cre_IndAudPropertyParm(Name),
7062    IAPP2 = cre_IndAudPropertyParm(Name2),
7063    IALCD = cre_IndAudLocalControlDesc('NULL', 'NULL', 'NULL',
7064				       [IAPP, IAPP2]),
7065    IASP  = cre_IndAudStreamParms(IALCD),
7066    SID   = 123,
7067    IASD  = cre_IndAudStreamDesc(SID, IASP),
7068    msg51(Mid, [IASD]).
7069
7070
7071%% IndAudEventsDescriptor:
7072msg52() ->
7073    msg52(?MG2_MID).
7074msg52(Mid) ->
7075    RequestID = 1235,
7076    PkgdName  = "tonedet/std",
7077    IAED = cre_IndAudEvsDesc(RequestID, PkgdName),
7078    IAP  = cre_IndAudParam(IAED),
7079    APT  = [IAP],
7080    msg50(Mid, APT).
7081
7082%% IndAudEventBufferDescriptor:
7083msg53() ->
7084    msg53(?MG2_MID).
7085msg53(Mid) ->
7086    EN    = "tonedet/std",
7087    SID   = 1,
7088    IAEBD = cre_IndAudEvBufDesc(EN, SID),
7089    IAP   = cre_IndAudParam(IAEBD),
7090    APT   = [IAP],
7091    msg50(Mid, APT).
7092
7093%% IndAudSignalsDescriptor:
7094msg54(Mid, Sig) ->
7095    IASD = cre_IndAudSigsDesc(Sig),
7096    IAP  = cre_IndAudParam(IASD),
7097    APT  = [IAP],
7098    msg50(Mid, APT).
7099
7100msg54a() ->
7101    msg54a(?MG2_MID).
7102msg54a(Mid) ->
7103    SN  = "tonegen/pt",
7104    Sig = cre_IndAudSig(SN),
7105    msg54(Mid, Sig).
7106
7107msg54b() ->
7108    msg54b(?MG2_MID).
7109msg54b(Mid) ->
7110    SN  = "dg/d0",
7111    Sig = cre_IndAudSig(SN),
7112    msg54(Mid, Sig).
7113
7114msg54c() ->
7115    msg54c(?MG2_MID).
7116msg54c(Mid) ->
7117    SN  = "ct/ct",
7118    Sig = cre_IndAudSig(SN),
7119    ID  = 4321,
7120    SSL = cre_IndAudSeqSigList(ID, Sig),
7121    msg54(Mid, SSL).
7122
7123%% IndAudDigitMapDescriptor:
7124msg55() ->
7125    msg55(?MG2_MID).
7126msg55(Mid) ->
7127    DMN   = "dialplan00",
7128    IADMD = cre_IndAudDigitMapDesc(DMN),
7129    IAP   = cre_IndAudParam(IADMD),
7130    APT   = [IAP],
7131    msg50(Mid, APT).
7132
7133%% IndAudStatisticsDescriptor:
7134msg56() ->
7135    msg56(?MG2_MID).
7136msg56(Mid) ->
7137    SN   = "nt/dur",
7138    IASD = cre_IndAudStatsDesc(SN),
7139    IAP  = cre_IndAudParam(IASD),
7140    APT  = [IAP],
7141    msg50(Mid, APT).
7142
7143%% IndAudPackagesDescriptor:
7144msg57() ->
7145    msg57(?MG2_MID).
7146msg57(Mid) ->
7147    PN   = "al",
7148    PV   = 1,
7149    IAPD = cre_IndAudPkgsDesc(PN, PV),
7150    IAP  = cre_IndAudParam(IAPD),
7151    APT  = [IAP],
7152    msg50(Mid, APT).
7153
7154%% Sum it up:
7155msg58_iaMediaDesc_iap(IATSD) ->
7156    IAMD  = cre_IndAudMediaDesc(IATSD),
7157    cre_IndAudParam(IAMD).
7158
7159msg58_iaMediaDesc_iap_a() ->
7160    PP    = cre_IndAudPropertyParm("tdmc/gain"),
7161    PPs   = [PP],
7162    IATSD = cre_IndAudTermStateDesc(PPs),
7163    msg58_iaMediaDesc_iap(IATSD).
7164
7165msg58_iaMediaDesc_iap_b() ->
7166    IATSD = cre_IndAudTermStateDesc([], 'NULL', asn1_NOVALUE),
7167    msg58_iaMediaDesc_iap(IATSD).
7168
7169msg58_iaEvsDesc_iap() ->
7170    RequestID = 1235,
7171    PkgdName  = "tonedet/std",
7172    IAED = cre_IndAudEvsDesc(RequestID, PkgdName),
7173    cre_IndAudParam(IAED).
7174
7175msg58_iaEvBufDesc_iap() ->
7176    EN    = "tonedet/std",
7177    SID   = 1,
7178    IAEBD = cre_IndAudEvBufDesc(EN, SID),
7179    cre_IndAudParam(IAEBD).
7180
7181msg58_iaSigsDesc_iap(S) ->
7182    IASD = cre_IndAudSigsDesc(S),
7183    cre_IndAudParam(IASD).
7184
7185msg58_iaSigsDesc_iap_a() ->
7186    SN  = "tonegen/pt",
7187    Sig = cre_IndAudSig(SN),
7188    msg58_iaSigsDesc_iap(Sig).
7189
7190msg58_iaSigsDesc_iap_b() ->
7191    SN  = "ct/ct",
7192    Sig = cre_IndAudSig(SN),
7193    ID  = 4321,
7194    SSL = cre_IndAudSeqSigList(ID, Sig),
7195    msg58_iaSigsDesc_iap(SSL).
7196
7197msg58_iaDigMapDesc_iap() ->
7198    DMN   = "dialplan00",
7199    IADMD = cre_IndAudDigitMapDesc(DMN),
7200    cre_IndAudParam(IADMD).
7201
7202msg58_iaStatsDesc_iap() ->
7203    SN   = "nt/dur",
7204    IASD = cre_IndAudStatsDesc(SN),
7205    cre_IndAudParam(IASD).
7206
7207msg58_iaPacksDesc_iap() ->
7208    PN   = "al",
7209    PV   = 1,
7210    IAPD = cre_IndAudPkgsDesc(PN, PV),
7211    cre_IndAudParam(IAPD).
7212
7213msg58a() ->
7214    msg58a(?MG2_MID).
7215msg58a(Mid) ->
7216    IAMD  = msg58_iaMediaDesc_iap_a(),
7217    IAED  = msg58_iaEvsDesc_iap(),
7218    IAEBD = msg58_iaEvBufDesc_iap(),
7219    IASiD = msg58_iaSigsDesc_iap_a(),
7220    IADMD = msg58_iaDigMapDesc_iap(),
7221    IAStD = msg58_iaStatsDesc_iap(),
7222    IAPD  = msg58_iaPacksDesc_iap(),
7223    APT   = [IAMD, IAED, IAEBD, IASiD, IADMD, IAStD, IAPD],
7224    msg50(Mid, APT).
7225
7226msg58b() ->
7227    msg58b(?MG2_MID).
7228msg58b(Mid) ->
7229    IAMD  = msg58_iaMediaDesc_iap_b(),
7230    IAED  = msg58_iaEvsDesc_iap(),
7231    IAEBD = msg58_iaEvBufDesc_iap(),
7232    IASiD = msg58_iaSigsDesc_iap_b(),
7233    IADMD = msg58_iaDigMapDesc_iap(),
7234    IAStD = msg58_iaStatsDesc_iap(),
7235    IAPD  = msg58_iaPacksDesc_iap(),
7236    APT   = [IAMD, IAED, IAEBD, IASiD, IADMD, IAStD, IAPD],
7237    msg50(Mid, APT).
7238
7239
7240%% - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
7241%% Tests some of the changes in the v2 corr 1 (EmergencyOff and ModemDesc)
7242
7243%% Emergency On/Off (optional) tests
7244msg61(EM) ->
7245    TS     = cre_TimeNot("19990729", "22000000"),
7246    Event  = cre_ObsEv("al/of",TS),
7247    Desc   = cre_ObsEvsDesc(2222,[Event]),
7248    NotReq = cre_NotifyReq([#megaco_term_id{id = ?A4444}],Desc),
7249    Cmd    = ?MSG_LIB:cre_Command(notifyReq, NotReq),
7250    CmdReq = cre_CmdReq(Cmd),
7251    CtxReq = ?MSG_LIB:cre_ContextRequest(15, EM),
7252    ActReq = ?MSG_LIB:cre_ActionRequest(1, CtxReq, [CmdReq]),
7253    Acts   = [ActReq],
7254    TR     = ?MSG_LIB:cre_TransactionRequest(9898, Acts),
7255    Trans  = ?MSG_LIB:cre_Transaction(TR),
7256    Mess   = ?MSG_LIB:cre_Message(?VERSION, ?MG1_MID, [Trans]),
7257    ?MSG_LIB:cre_MegacoMessage(Mess).
7258
7259msg61a() ->
7260    msg61(false).
7261
7262msg61b() ->
7263    msg61(true).
7264
7265msg61c() ->
7266    msg61(asn1_NOVALUE).
7267
7268
7269msg62a() ->
7270    MT      = ?MSG_LIB:cre_ModemType(v18),
7271    PP      = cre_PropParm("c", "IN IP4 $ "),
7272    MD      = ?MSG_LIB:cre_ModemDescriptor([MT], [PP]),
7273    AmmDesc = ?MSG_LIB:cre_AmmDescriptor(MD),
7274    TermIDs = [#megaco_term_id{id = ?A4444}],
7275    AmmReq  = ?MSG_LIB:cre_AmmRequest(TermIDs, [AmmDesc]),
7276    Cmd     = ?MSG_LIB:cre_Command(addReq, AmmReq),
7277    CmdReq  = ?MSG_LIB:cre_CommandRequest(Cmd),
7278    ActReq  = ?MSG_LIB:cre_ActionRequest(2, [CmdReq]),
7279    Acts    = [ActReq],
7280    TR      = ?MSG_LIB:cre_TransactionRequest(9898, Acts),
7281    Trans   = ?MSG_LIB:cre_Transaction(TR),
7282    Mess    = ?MSG_LIB:cre_Message(?VERSION, ?MG1_MID, [Trans]),
7283    ?MSG_LIB:cre_MegacoMessage(Mess).
7284
7285msg62b() ->
7286    MP =
7287"MEGACO/" ?VERSION_STR " [124.124.124.222]:55555
7288Transaction = 9898 {
7289        Context = 2 {
7290                Add = 11111111/00000000/00000000 {
7291                        Modem[V18] {
7292                                tdmc/gain=2
7293                        }
7294                }
7295        }
7296}",
7297%     MC =
7298% "!/" ?VERSION_STR " [124.124.124.222]:55555\nT=9898{C=2{A=11111111/00000000/00000000{MD[V18]{tdmc/gain=2}}}}",
7299    list_to_binary(MP).
7300
7301%% - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
7302%% Pretty RFC 3525 messages:
7303
7304%% Added Reason
7305rfc3525_msg1() ->
7306"MEGACO/" ?VERSION_STR " [124.124.124.222] Transaction = 9998 {
7307   Context = - {
7308      ServiceChange = ROOT {
7309         Services {
7310            Method = Restart,
7311            Reason = 901,
7312            ServiceChangeAddress = 55555,
7313            Profile = ResGW/1
7314         }
7315      }
7316   }
7317}".
7318
7319rfc3525_msg2() ->
7320"MEGACO/" ?VERSION_STR " [123.123.123.4]:55555 Reply = 9998 {
7321   Context = - {
7322      ServiceChange = ROOT {
7323         Services {
7324            ServiceChangeAddress = 55555,
7325            Profile = ResGW/1
7326         }
7327      }
7328   }
7329}".
7330
7331
7332%% Removed "," after LocalControl ending "}"
7333rfc3525_msg3() ->
7334"MEGACO/" ?VERSION_STR " [123.123.123.4]:55555 Transaction = 9999 {
7335   Context = - {
7336      Modify = A4444 {
7337         Media {
7338            Stream = 1 {
7339               LocalControl {
7340                  Mode = SendReceive,
7341                  tdmc/gain=2,  ; in dB,
7342                  tdmc/ec=on
7343               }
7344            }
7345         },
7346         Events = 2222 {
7347            al/of {strict=state}
7348         }
7349      }
7350   }
7351}".
7352
7353%% Removed the outermost "{}" pair (before the Reply token)
7354rfc3525_msg4() ->
7355"MEGACO/" ?VERSION_STR " [124.124.124.222]:55555 Reply = 9999 {
7356   Context = - {
7357      Modify = A4444
7358   }
7359}".
7360
7361rfc3525_msg6() ->
7362"MEGACO/" ?VERSION_STR " [124.124.124.222]:55555 Transaction = 10000 {
7363   Context = - {
7364      Notify = A4444 {
7365         ObservedEvents =2222 {
7366            19990729T22000000:al/of{init=false}
7367         }
7368      }
7369   }
7370}".
7371
7372
7373rfc3525_msg7() ->
7374"MEGACO/" ?VERSION_STR " [123.123.123.4]:55555 Reply = 10000 {
7375   Context = - {
7376      Notify = A4444
7377   }
7378}".
7379
7380rfc3525_msg8() ->
7381"MEGACO/" ?VERSION_STR " [123.123.123.4]:55555 Transaction = 10001 {
7382   Context = - {
7383      Modify = A4444 {
7384         Events = 2223 {
7385            al/on {strict=state},
7386            dd/ce {DigitMap=Dialplan0}
7387	 },
7388         Signals {cg/dt},
7389         DigitMap = Dialplan0 {
7390            (0| 00|[1-7]xxx|8xxxxxxx|fxxxxxxx|exx|91xxxxxxxxxx|9011x.)
7391         }
7392      }
7393   }
7394}".
7395
7396rfc3525_msg9() ->
7397"MEGACO/" ?VERSION_STR " [124.124.124.222]:55555 Reply = 10001 {
7398   Context = - {
7399      Modify = A4444
7400   }
7401}".
7402
7403rfc3525_msg10() ->
7404"MEGACO/" ?VERSION_STR " [124.124.124.222]:55555 Transaction = 10002 {
7405   Context = - {
7406      Notify = A4444 {
7407         ObservedEvents =2223 {
7408            19990729T22010001:dd/ce {
7409               ds=\"916135551212\",
7410               Meth=UM
7411            }
7412         }
7413      }
7414   }
7415}".
7416
7417
7418rfc3525_msg11() ->
7419"MEGACO/" ?VERSION_STR " [123.123.123.4]:55555 Reply = 10002 {
7420   Context = - {
7421      Notify = A4444
7422   }
7423}".
7424
7425%% Added ?
7426rfc3525_msg12() ->
7427"MEGACO/" ?VERSION_STR " [123.123.123.4]:55555 Transaction = 10003 {
7428   Context = $ {
7429      Add = A4444,
7430      Add = $ {
7431         Media {
7432            Stream = 1 {
7433               LocalControl {
7434                  Mode = ReceiveOnly,
7435                  nt/jit=40 ; in ms
7436               },
7437               Local {
7438                  v=0 c=IN IP4 $ m=audio $ RTP/AVP 4 a=ptime:30 v=0 c=IN IP4 $ m=audio $ RTP/AVP 0
7439               }
7440            }
7441         }
7442      }
7443   }
7444}".
7445
7446%% Added ?
7447rfc3525_msg13() ->
7448"MEGACO/" ?VERSION_STR " [124.124.124.222]:55555 Reply = 10003 {
7449   Context = 2000 {
7450      Add = A4444,
7451      Add = A4445 {
7452         Media {
7453            Stream = 1 {
7454               Local {
7455v=0
7456o=- 2890844526 2890842807 IN IP4 124.124.124.222
7457s=-
7458t= 0 0
7459c=IN IP4 124.124.124.222
7460m=audio 2222 RTP/AVP 4
7461a=ptime:30
7462a=recvonly
7463               } ; RTP profile for G.723.1 is 4
7464            }
7465         }
7466      }
7467   }
7468}".
7469
7470%%
7471%% Added ?
7472rfc3525_msg14() ->
7473"MEGACO/" ?VERSION_STR " [123.123.123.4]:55555 Transaction = 50003 {
7474   Context = $ {
7475      Add = A5555 {
7476         Media {
7477            Stream = 1 {
7478               LocalControl {
7479                  Mode = SendReceive
7480               }
7481            }
7482         },
7483         Events = 1234 {
7484            al/of {strict=state}
7485         },
7486         Signals {al/ri}
7487      },
7488      Add = $ {
7489         Media {
7490            Stream = 1 {
7491               LocalControl {
7492                  Mode = SendReceive,
7493                  nt/jit=40 ; in ms
7494               },
7495               Local {
7496                  v=0 c=IN IP4 $ m=audio $ RTP/AVP 4 a=ptime:30
7497               },
7498               Remote {
7499                  v=0 c=IN IP4 124.124.124.222 m=audio 2222 RTP/AVP 4 a=ptime:30
7500               } ; RTP profile for G.723.1 is 4
7501            }
7502         }
7503      }
7504   }
7505}".
7506
7507%% Added ?
7508rfc3525_msg15() ->
7509"MEGACO/" ?VERSION_STR " [125.125.125.111]:55555 Reply = 50003 {
7510   Context = 5000 {
7511      Add = A5555,
7512      Add = A5556 {
7513         Media {
7514            Stream = 1 {
7515               Local {
7516                  v=0 o=- 7736844526 7736842807 IN IP4 125.125.125.111 s=- t= 0 0 c=IN IP4 125.125.125.111 m=audio 1111 RTP/AVP 4
7517               } ; RTP profile for G723.1 is 4
7518            }
7519         }
7520      }
7521   }
7522}".
7523
7524%% Added ?
7525rfc3525_msg16a() ->
7526"MEGACO/" ?VERSION_STR " [123.123.123.4]:55555 Transaction = 10005 {
7527   Context = 2000 {
7528      Modify = A4444 {
7529         Signals {cg/rt}
7530      },
7531      Modify = A4445 {
7532         Media {
7533            Stream = 1 {
7534               Remote {
7535                  v=0 o=- 7736844526 7736842807 IN IP4 125.125.125.111 s=- t= 0 0 c=IN IP4 125.125.125.111 m=audio 1111 RTP/AVP 4
7536	       } ; RTP profile for G723.1 is 4
7537            }
7538         }
7539      }
7540   }
7541}".
7542
7543rfc3525_msg16b() ->
7544"MEGACO/" ?VERSION_STR " [124.124.124.222]:55555 Reply = 10005 {
7545   Context = 2000 {
7546      Modify = A4444,
7547      Modify = A4445
7548   }
7549}".
7550
7551rfc3525_msg17a() ->
7552"MEGACO/" ?VERSION_STR " [125.125.125.111]:55555 Transaction = 50005 {
7553   Context = 5000 {
7554      Notify = A5555 {
7555         ObservedEvents = 1234 {
7556            19990729T22020002:al/of{init=false}
7557         }
7558      }
7559   }
7560}".
7561
7562rfc3525_msg17b() ->
7563"MEGACO/" ?VERSION_STR " [123.123.123.4]:55555 Reply = 50005 {
7564   Context = - {
7565      Notify = A5555
7566   }
7567}".
7568
7569%% Removed "{ }" after Signals
7570rfc3525_msg17c() ->
7571"MEGACO/" ?VERSION_STR " [123.123.123.4]:55555 Transaction = 50006 {
7572   Context = 5000 {
7573      Modify = A5555 {
7574         Events = 1235 {
7575            al/on{strict=state}
7576         },
7577         Signals ; to turn off ringing
7578      }
7579   }
7580}".
7581
7582rfc3525_msg17d() ->
7583"MEGACO/" ?VERSION_STR " [125.125.125.111]:55555 Reply = 50006 {
7584   Context = 5000 {
7585      Modify = A4445
7586   }
7587}".
7588
7589%% Removed "{ }" after Signals
7590rfc3525_msg18a() ->
7591"MEGACO/" ?VERSION_STR " [123.123.123.4]:55555 Transaction = 10006 {
7592   Context = 2000 {
7593      Modify = A4445 {
7594         Media {
7595            Stream = 1 {
7596               LocalControl {
7597                  Mode = SendReceive
7598               }
7599            }
7600         }
7601      },
7602      Modify = A4444 {
7603         Signals
7604      }
7605   }
7606}".
7607
7608rfc3525_msg18b() ->
7609"MEGACO/" ?VERSION_STR " [124.124.124.222]:55555 Reply = 10006 {
7610   Context = 2000 {
7611      Modify = A4445,
7612      Modify = A4444
7613   }
7614}".
7615
7616rfc3525_msg19() ->
7617"MEGACO/" ?VERSION_STR " [123.123.123.4]:55555 Transaction = 50007 {
7618   Context = - {
7619      AuditValue = A5556 {
7620         Audit {
7621            Media, DigitMap, Events, Signals, Packages, Statistics
7622         }
7623      }
7624   }
7625}".
7626
7627%% Added ?
7628rfc3525_msg20() ->
7629"MEGACO/" ?VERSION_STR " [125.125.125.111]:55555 Reply = 50007 {
7630   Context = - {
7631      AuditValue = A5556 {
7632         Media {
7633            TerminationState {
7634               ServiceStates = InService,
7635               Buffer = OFF
7636            },
7637            Stream = 1 {
7638               LocalControl {
7639                  Mode = SendReceive,
7640                  nt/jit=40
7641               },
7642               Local {
7643                  v=0 o=- 7736844526 7736842807 IN IP4 125.125.125.111 s=- t= 0 0 c=IN IP4 125.125.125.111 m=audio 1111 RTP/AVP  4 a=ptime:30
7644               },
7645               Remote {
7646                  v=0 o=- 2890844526 2890842807 IN IP4 124.124.124.222 s=- t= 0 0 c=IN IP4 124.124.124.222 m=audio 2222 RTP/AVP  4 a=ptime:30
7647               }
7648            }
7649         },
7650         Events,
7651         Signals,
7652         DigitMap,
7653         Packages {nt-1, rtp-1},
7654         Statistics {
7655            rtp/ps=1200,  ; packets sent
7656            nt/os=62300, ; octets sent
7657            rtp/pr=700, ; packets received
7658            nt/or=45100, ; octets received
7659            rtp/pl=0.2,  ; % packet loss
7660            rtp/jit=20,
7661            rtp/delay=40 ; avg latency
7662         }
7663      }
7664   }
7665}".
7666
7667rfc3525_msg21a() ->
7668"MEGACO/" ?VERSION_STR " [125.125.125.111]:55555 Transaction = 50008 {
7669   Context = 5000 {
7670      Notify = A5555 {
7671         ObservedEvents =1235 {
7672            19990729T24020002:al/on {init=false}
7673         }
7674      }
7675   }
7676}".
7677
7678rfc3525_msg21b() ->
7679"MEGACO/" ?VERSION_STR " [123.123.123.4]:55555 Reply = 50008 {
7680   Context = - {
7681      Notify = A5555
7682   }
7683}".
7684
7685rfc3525_msg22a() ->
7686"MEGACO/" ?VERSION_STR " [123.123.123.4]:55555 Transaction = 50009 {
7687   Context = 5000 {
7688      Subtract = A5555 {
7689         Audit {
7690            Statistics
7691         }
7692      },
7693      Subtract = A5556 {
7694         Audit {
7695            Statistics
7696         }
7697      }
7698   }
7699}".
7700
7701%% Added ?
7702rfc3525_msg22b() ->
7703"MEGACO/" ?VERSION_STR " [125.125.125.111]:55555 Reply = 50009 {
7704   Context = 5000 {
7705      Subtract = A5555 {
7706         Statistics {
7707            nt/os=45123, ; Octets Sent
7708            nt/dur=40 ; in seconds
7709         }
7710      },
7711      Subtract = A5556 {
7712         Statistics {
7713            rtp/ps=1245, ; packets sent
7714            nt/os=62345, ; octets sent
7715            rtp/pr=780, ; packets received
7716            nt/or=45123, ; octets received
7717            rtp/pl=10, ;  % packets lost
7718            rtp/jit=27,
7719            rtp/delay=48 ; average latency
7720         }
7721      }
7722   }
7723}".
7724
7725rfc3525_msgs() ->
7726    [
7727     {msg1,   rfc3525_msg1()},
7728     {msg2,   rfc3525_msg2()},
7729     {msg3,   rfc3525_msg3()},
7730     {msg4,   rfc3525_msg4()},
7731     {msg6,   rfc3525_msg6()},
7732     {msg7,   rfc3525_msg7()},
7733     {msg8,   rfc3525_msg8()},
7734     {msg9,   rfc3525_msg9()},
7735     {msg10,  rfc3525_msg10()},
7736     {msg11,  rfc3525_msg11()},
7737     {msg12,  rfc3525_msg12()},
7738     {msg13,  rfc3525_msg13()},
7739     {msg14,  rfc3525_msg14()},
7740     {msg15,  rfc3525_msg15()},
7741     {msg16a, rfc3525_msg16a()},
7742     {msg16b, rfc3525_msg16b()},
7743     {msg17a, rfc3525_msg17a()},
7744     {msg17b, rfc3525_msg17b()},
7745     {msg17c, rfc3525_msg17c()},
7746     {msg17d, rfc3525_msg17d()},
7747     {msg18a, rfc3525_msg18a()},
7748     {msg18b, rfc3525_msg18b()},
7749     {msg19,  rfc3525_msg19()},
7750     {msg20,  rfc3525_msg20()},
7751     {msg21a, rfc3525_msg21a()},
7752     {msg21b, rfc3525_msg21b()},
7753     {msg22a, rfc3525_msg22a()},
7754     {msg22b, rfc3525_msg22b()}
7755    ].
7756
7757rfc3525_msgs_display() ->
7758    Msgs = rfc3525_msgs(),
7759    Fun = fun({Name, Msg}) ->
7760		  io:format("~w: ~n~s~n~n", [Name, Msg])
7761	  end,
7762    lists:foreach(Fun, Msgs).
7763
7764rfc3525_msgs_test() ->
7765    put(dbg,true),
7766    Res = rfc3525_msgs_test(megaco_pretty_text_encoder, [], 2),
7767    erase(dbg),
7768    io:format("~w~n", [Res]).
7769
7770rfc3525_msgs_test(Codec, Config, Ver) ->
7771    io:format("-----------------------------------------"
7772	      "~ntesting with"
7773	      "~n   Codec:   ~w"
7774	      "~n   Config:  ~w"
7775	      "~n   Version: ~w"
7776	      "~n", [Codec, Config, Ver]),
7777    Msgs = rfc3525_msgs(),
7778    Test = fun({N,M1}) ->
7779		   %% io:format("testing ~w: ", [N]),
7780		   io:format("~n*** testing ~w *** ~n~s~n", [N,M1]),
7781		   Bin1 = erlang:list_to_binary(M1),
7782		   case (catch Codec:decode_message(Config, Ver, Bin1)) of
7783		       {ok, M2} ->
7784			   %% io:format("d", []),
7785			   io:format("decoded:~n~p~n", [M2]),
7786			   case (catch Codec:encode_message(Config, Ver, M2)) of
7787			       {ok, Bin2} when is_binary(Bin2) ->
7788				   %% io:format("e~n", []),
7789				   io:format("encode: ~n~s~n", [erlang:binary_to_list(Bin2)]),
7790				   {N,ok};
7791			       {ok, M3} ->
7792				   %% io:format("e~n", []),
7793				   io:format("encode: ~n~s~n", [M3]),
7794				   {N,ok};
7795			       E ->
7796				   io:format("~n~p~n", [E]),
7797				   {N,encode_error}
7798			   end;
7799		       E ->
7800			   io:format("~n~p~n", [E]),
7801			   {N,decode_error}
7802		   end
7803	  end,
7804    [Test(M) || M <- Msgs].
7805
7806
7807%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
7808
7809skip(Reason) ->
7810    megaco_codec_test_lib:skip(Reason).
7811
7812%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
7813
7814decode_message(Codec, DynamicDecode, Conf, Bin) ->
7815    megaco_codec_test_lib:decode_message(Codec, DynamicDecode, ?VERSION,
7816					 Conf, Bin).
7817encode_message(Codec, Conf, Msg) ->
7818    megaco_codec_test_lib:encode_message(Codec, ?VERSION, Conf, Msg).
7819
7820test_msgs(Codec, DynamicDecode, Conf, Msgs) ->
7821    megaco_codec_test_lib:test_msgs(Codec, DynamicDecode, ?VERSION, Conf,
7822				    fun chk_MegacoMessage/2, Msgs).
7823
7824
7825%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
7826
7827decode_mini_message(Codec, Conf, Bin) ->
7828    Codec:decode_mini_message(Conf, dynamic, Bin).
7829
7830
7831%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
7832
7833chk_MegacoMessage(M1, M2) ->
7834    ?MSG_LIB:chk_MegacoMessage(M1, M2).
7835
7836
7837%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
7838
7839cre_MegacoMessage(Mess) ->
7840    ?MSG_LIB:cre_MegacoMessage(Mess).
7841
7842cre_MegacoMessage(V, Mid, Body) ->
7843    Mess = ?MSG_LIB:cre_Message(V, Mid, Body),
7844    ?MSG_LIB:cre_MegacoMessage(Mess).
7845
7846cre_AuthHeader() ->
7847    SecParmIdx = [239, 205, 171, 137],
7848    SeqNum     = [18, 52, 86, 120],
7849    AD         = [18, 52, 86, 120, 137, 171, 205, 239, 118, 84, 50, 16],
7850    cre_AuthHeader(SecParmIdx, SeqNum, AD).
7851
7852cre_Msg(Mid, Body) ->
7853    cre_Msg(?VERSION, Mid, Body).
7854
7855cre_Msg(V, Mid, Body) ->
7856    ?MSG_LIB:cre_Message(V, Mid, Body).
7857
7858cre_AuthHeader(Idx, Num, D) ->
7859    ?MSG_LIB:cre_AuthenticationHeader(Idx, Num, D).
7860
7861cre_TransId(TransId) ->
7862    ?MSG_LIB:cre_TransactionId(TransId).
7863
7864cre_Trans(Trans) ->
7865    ?MSG_LIB:cre_Transaction(Trans).
7866
7867cre_TransReq(TransId, Actions) ->
7868    ?MSG_LIB:cre_TransactionRequest(TransId, Actions).
7869
7870cre_TransRep(TransId, Actions) ->
7871    ?MSG_LIB:cre_TransactionReply(TransId, Actions).
7872
7873cre_TransAck(First, Last) ->
7874    ?MSG_LIB:cre_TransactionAck(First, Last).
7875
7876cre_ActReq(CtxId, CmdReqs) ->
7877    ?MSG_LIB:cre_ActionRequest(CtxId, CmdReqs).
7878
7879cre_ActRep(CtxId, CmdReply) ->
7880    ?MSG_LIB:cre_ActionReply(CtxId, CmdReply).
7881
7882cre_CtxID(Id) ->
7883    ?MSG_LIB:cre_ContextID(Id).
7884
7885%% Ind Aud related:
7886
7887cre_IndAudParam(IAP) ->
7888    ?MSG_LIB:cre_IndAuditParameter(IAP).
7889
7890cre_IndAudMediaDesc(D) ->
7891    ?MSG_LIB:cre_IndAudMediaDescriptor(D).
7892
7893cre_IndAudStreamDesc(SID, SP) ->
7894    ?MSG_LIB:cre_IndAudStreamDescriptor(SID, SP).
7895
7896cre_IndAudStreamParms(LCD) ->
7897    ?MSG_LIB:cre_IndAudStreamParms(LCD).
7898
7899cre_IndAudLocalControlDesc(SM, RV, RG, PP) ->
7900    ?MSG_LIB:cre_IndAudLocalControlDescriptor(SM, RV, RG, PP).
7901
7902cre_IndAudPropertyParm(Name) ->
7903    ?MSG_LIB:cre_IndAudPropertyParm(Name).
7904
7905cre_IndAudTermStateDesc(PP) ->
7906    ?MSG_LIB:cre_IndAudTerminationStateDescriptor(PP).
7907
7908cre_IndAudTermStateDesc(PP, EBC, SS) ->
7909    ?MSG_LIB:cre_IndAudTerminationStateDescriptor(PP, EBC, SS).
7910
7911cre_IndAudEvsDesc(RID, PN)
7912  when is_integer(RID) ->
7913    ?MSG_LIB:cre_IndAudEventsDescriptor(RID, PN).
7914
7915cre_IndAudEvBufDesc(EN, SID) ->
7916    ?MSG_LIB:cre_IndAudEventBufferDescriptor(EN, SID).
7917
7918cre_IndAudSigsDesc(D) ->
7919    ?MSG_LIB:cre_IndAudSignalsDescriptor(D).
7920
7921cre_IndAudSig(SN) ->
7922    ?MSG_LIB:cre_IndAudSignal(SN).
7923
7924cre_IndAudSeqSigList(ID, SL) ->
7925    ?MSG_LIB:cre_IndAudSeqSigList(ID, SL).
7926
7927cre_IndAudDigitMapDesc(DMN) ->
7928    ?MSG_LIB:cre_IndAudDigitMapDescriptor(DMN).
7929
7930cre_IndAudStatsDesc(SN) ->
7931    ?MSG_LIB:cre_IndAudStatisticsDescriptor(SN).
7932
7933cre_IndAudPkgsDesc(PN, PV) ->
7934    ?MSG_LIB:cre_IndAudPackagesDescriptor(PN, PV).
7935
7936%% Parameter related
7937cre_PropParm(Name, Val) ->
7938    ?MSG_LIB:cre_PropertyParm(Name, [Val]).
7939
7940
7941%% Statistics related
7942cre_StatsParm(Name, Val) ->
7943    ?MSG_LIB:cre_StatisticsParameter(Name, [Val]).
7944
7945
7946% Event related
7947cre_EvParm(Name, Val) ->
7948    ?MSG_LIB:cre_EventParameter(Name, Val).
7949
7950cre_ObsEv(Name, Not) ->
7951    ?MSG_LIB:cre_ObservedEvent(Name, Not).
7952cre_ObsEv(Name, Not, Par) ->
7953    ?MSG_LIB:cre_ObservedEvent(Name, Par, Not).
7954
7955cre_ReqedEv(Name) ->
7956    ?MSG_LIB:cre_RequestedEvent(Name).
7957cre_ReqedEv(Name, Action) ->
7958    ?MSG_LIB:cre_RequestedEvent(Name, Action).
7959
7960
7961cre_ObsEvsDesc(Id, EvList) ->
7962    ?MSG_LIB:cre_ObservedEventsDescriptor(Id, EvList).
7963
7964cre_EvsDesc(Id, EvList) ->
7965    ?MSG_LIB:cre_EventsDescriptor(Id, EvList).
7966
7967
7968%% Service change related
7969cre_SvcChParm(M, A, R, P) ->
7970    ?MSG_LIB:cre_ServiceChangeParm(M, A, P, R).
7971
7972cre_SvcChResParm(A, P) ->
7973    ?MSG_LIB:cre_ServiceChangeResParm(A, P).
7974
7975cre_SvcChReq(Tids, P) ->
7976    ?MSG_LIB:cre_ServiceChangeRequest(Tids, P).
7977
7978cre_SvcChProf(Name, Ver) ->
7979    ?MSG_LIB:cre_ServiceChangeProfile(Name, Ver).
7980
7981cre_SvcChRep(Tids, Res) ->
7982    ?MSG_LIB:cre_ServiceChangeReply(Tids, Res).
7983
7984
7985%% Stream related
7986cre_StreamParms(Lcd) ->
7987    ?MSG_LIB:cre_StreamParms(Lcd).
7988cre_StreamParms(Lcd, Ld) ->
7989    ?MSG_LIB:cre_StreamParms(Lcd, Ld).
7990cre_StreamParms(Lcd, Ld, Rd) ->
7991    ?MSG_LIB:cre_StreamParms(Lcd, Ld, Rd).
7992cre_StreamParmsL(Ld) ->
7993    ?MSG_LIB:cre_StreamParms(asn1_NOVALUE, Ld, asn1_NOVALUE).
7994cre_StreamParmsR(Rd) ->
7995    ?MSG_LIB:cre_StreamParms(asn1_NOVALUE, asn1_NOVALUE, Rd).
7996
7997cre_StreamDesc(Id, P) ->
7998    ?MSG_LIB:cre_StreamDescriptor(Id, P).
7999
8000
8001%% "Local" related
8002cre_LocalControlDesc(Mode) ->
8003    ?MSG_LIB:cre_LocalControlDescriptor(Mode).
8004cre_LocalControlDesc(Mode, Parms) ->
8005    ?MSG_LIB:cre_LocalControlDescriptor(Mode, Parms).
8006
8007cre_LocalRemoteDesc(Grps) ->
8008    ?MSG_LIB:cre_LocalRemoteDescriptor(Grps).
8009
8010
8011%% DigitMap related
8012cre_DigitMapDesc() ->
8013    ?MSG_LIB:cre_DigitMapDescriptor().
8014cre_DigitMapDesc(NameOrVal) ->
8015    ?MSG_LIB:cre_DigitMapDescriptor(NameOrVal).
8016cre_DigitMapDesc(Name, Val) ->
8017    ?MSG_LIB:cre_DigitMapDescriptor(Name, Val).
8018
8019cre_DigitMapValue(Body) ->
8020    ?MSG_LIB:cre_DigitMapValue(Body).
8021
8022cre_DigitMapValue(Body, Start, Short, Long) ->
8023    ?MSG_LIB:cre_DigitMapValue(Start, Short, Long, Body).
8024
8025%% Media related
8026cre_MediaDesc(SD) when is_record(SD, 'StreamDescriptor') ->
8027    cre_MediaDesc([SD]);
8028cre_MediaDesc(SDs) ->
8029    ?MSG_LIB:cre_MediaDescriptor(SDs).
8030
8031
8032%% Notify related
8033cre_NotifyReq(Tids, EvsDesc) ->
8034    ?MSG_LIB:cre_NotifyRequest(Tids, EvsDesc).
8035
8036cre_NotifyRep(Tids) ->
8037    ?MSG_LIB:cre_NotifyReply(Tids).
8038
8039
8040%% Subtract related
8041cre_SubReq(Tids, Desc) ->
8042    ?MSG_LIB:cre_SubtractRequest(Tids, Desc).
8043
8044
8045%% Audit related
8046cre_AuditDesc(Tokens) ->
8047    ?MSG_LIB:cre_AuditDescriptor(Tokens).
8048
8049cre_AuditDesc(Tokens, PropertTokens) ->
8050    ?MSG_LIB:cre_AuditDescriptor(Tokens, PropertTokens).
8051
8052cre_AuditReq(Tid, Desc) ->
8053    ?MSG_LIB:cre_AuditRequest(Tid, Desc).
8054
8055cre_AuditRes(Tid, Res) ->
8056    ?MSG_LIB:cre_AuditResult(Tid, Res).
8057
8058
8059%% AMM/AMMS related
8060cre_AmmReq(Tids, Descs) ->
8061    ?MSG_LIB:cre_AmmRequest(Tids, Descs).
8062
8063cre_AmmsReply(Tids) ->
8064    ?MSG_LIB:cre_AmmsReply(Tids).
8065cre_AmmsReply(Tids, Descs) ->
8066    ?MSG_LIB:cre_AmmsReply(Tids, Descs).
8067
8068
8069%% Command related
8070%% cre_command(Tag, Req) ->
8071%%     ?MSG_LIB:cre_Command(Tag, Req).
8072
8073cre_CmdReq(Cmd) ->
8074    ?MSG_LIB:cre_CommandRequest(Cmd).
8075
8076
8077%% Actions related
8078cre_ReqedActs(DmName) ->
8079    EDM = ?MSG_LIB:cre_EventDM(DmName),
8080    ?MSG_LIB:cre_RequestedActions(EDM).
8081
8082
8083%% Signal related
8084cre_Sig(Name) ->
8085    ?MSG_LIB:cre_Signal(Name).
8086
8087
8088%% Others
8089cre_TimeNot(D,T) ->
8090    ?MSG_LIB:cre_TimeNotation(D, T).
8091
8092cre_PkgsItem(Name, Ver) ->
8093    ?MSG_LIB:cre_PackagesItem(Name, Ver).
8094
8095
8096%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
8097
8098flex_init(Config) ->
8099    %% io:format("~w:flex_init -> entry with: "
8100    %% 	      "~n   Config: ~p"
8101    %% 	      "~n", [?MODULE, Config]),
8102    Res = megaco_codec_flex_lib:init(Config),
8103    %% io:format("~w:flex_init -> flex init result: "
8104    %% 	      "~n   Res: ~p"
8105    %% 	      "~n", [?MODULE, Res]),
8106    Res.
8107
8108flex_finish(Config) ->
8109    megaco_codec_flex_lib:finish(Config).
8110
8111flex_scanner_conf(Config) ->
8112    megaco_codec_flex_lib:scanner_conf(Config).
8113
8114start_flex_scanner() ->
8115    megaco_codec_flex_lib:start().
8116
8117stop_flex_scanner(Pid) ->
8118    megaco_codec_flex_lib:stop(Pid).
8119
8120
8121%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
8122
8123t(F,A) ->
8124    p(printable(get(severity),trc),trc,F,A).
8125
8126d(F,A) ->
8127    p(printable(get(severity),dbg),dbg,F,A).
8128
8129l(F,A) ->
8130    p(printable(get(severity),log),log,F,A).
8131
8132e(F,A) ->
8133    p(printable(get(severity),err),err,F,A).
8134
8135
8136printable(trc,_) ->
8137    true;
8138printable(dbg,trc) ->
8139    false;
8140printable(dbg,_) ->
8141    true;
8142printable(log,log) ->
8143    true;
8144printable(log,err) ->
8145    true;
8146printable(err,err) ->
8147    true;
8148printable(_,_) ->
8149    false.
8150
8151
8152image_of(trc) ->
8153    "T";
8154image_of(dbg) ->
8155    "D";
8156image_of(log) ->
8157    "L";
8158image_of(err) ->
8159    "E";
8160image_of(L) ->
8161    io_lib:format("~p",[L]).
8162
8163
8164p(true,L,F,A) ->
8165    io:format("~s: " ++ F ++ "~n", [image_of(L)|A]);
8166p(_,_,_,_) ->
8167    ok.
8168
8169
8170p(F, A) ->
8171    io:format("*** [~s] ***"
8172	      "~n   " ++ F ++ "~n",
8173	      [?FTS() | A]).
8174