~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/megaco/src/binary/megaco_binary_transformer_prev3c.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%% 
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%% 
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%% 
 
16
%%     $Id$
 
17
%%
 
18
%%----------------------------------------------------------------------
 
19
%% Purpose: Transform internal form of Megaco/H.248 messages
 
20
%%----------------------------------------------------------------------
 
21
 
 
22
-module(megaco_binary_transformer_prev3c).
 
23
 
 
24
-include_lib("megaco/include/megaco.hrl").
 
25
%% -include_lib("megaco/include/megaco_message.hrl").
 
26
-include_lib("megaco/include/megaco_message_prev3c.hrl").
 
27
-include_lib("megaco/src/engine/megaco_internal.hrl").
 
28
 
 
29
-export([tr_message/3, tr_transaction/3]).
 
30
 
 
31
-define(DEFAULT_NAME_RESOLVER, megaco_binary_name_resolver_prev3c).
 
32
 
 
33
-record(state, {mode,                 % verify | encode | decode
 
34
                resolver_module,      % 
 
35
                resolver_options}).
 
36
 
 
37
resolve(Type, Item, State, Constraint) ->
 
38
    case State#state.mode of
 
39
        verify ->
 
40
            Item;
 
41
        encode ->
 
42
            ?d("resolve(encode) -> encode: ~p",[Item]),
 
43
            Mod = State#state.resolver_module,
 
44
            Opt = State#state.resolver_options,
 
45
            EncodedItem = Mod:encode_name(Opt, Type, Item),
 
46
            ?d("resolve -> verify contraint for ~p",[EncodedItem]),
 
47
            verify_constraint(EncodedItem, Constraint);
 
48
        decode ->
 
49
            ?d("resolve(decode) -> verify contraint for ~p",[Item]),
 
50
            DecodedItem = verify_constraint(Item, Constraint),
 
51
            Mod = State#state.resolver_module,
 
52
            Opt = State#state.resolver_options,
 
53
            ?d("resolve(decode) -> decode: ~p",[DecodedItem]),
 
54
            Mod:decode_name(Opt, Type, DecodedItem)
 
55
    end.
 
56
 
 
57
verify_constraint(Item, valid) ->
 
58
    Item;
 
59
verify_constraint(Item, Constraint) when function(Constraint) ->
 
60
    Constraint(Item).
 
61
 
 
62
tr_message(MegaMsg, Mode, Config) ->
 
63
    case Config of
 
64
        [native] ->
 
65
            MegaMsg;
 
66
        [verify] ->
 
67
            State = #state{mode = verify},
 
68
            tr_MegacoMessage(MegaMsg, State);
 
69
        [] ->
 
70
            State = #state{mode             = Mode,
 
71
                           resolver_module  = ?DEFAULT_NAME_RESOLVER,
 
72
                           resolver_options = [8, 8, 8]},
 
73
            tr_MegacoMessage(MegaMsg, State);
 
74
        [{binary_name_resolver, {Module, Options}}] when atom(Module) ->
 
75
            State = #state{mode             = Mode, 
 
76
                           resolver_module  = Module, 
 
77
                           resolver_options = Options},
 
78
            tr_MegacoMessage(MegaMsg, State)
 
79
    end.
 
80
 
 
81
tr_transaction(Trans, Mode, Config) ->
 
82
    case Config of
 
83
        [native] ->
 
84
            Trans;
 
85
        [verify] ->
 
86
            State = #state{mode = verify},
 
87
            tr_Transaction(Trans, State);
 
88
        [] ->
 
89
            State = #state{mode             = Mode,
 
90
                           resolver_module  = ?DEFAULT_NAME_RESOLVER,
 
91
                           resolver_options = [8, 8, 8]},
 
92
            tr_Transaction(Trans, State);
 
93
        [{binary_name_resolver, {Module, Options}}] when atom(Module) ->
 
94
            State = #state{mode             = Mode, 
 
95
                           resolver_module  = Module, 
 
96
                           resolver_options = Options},
 
97
            tr_Transaction(Trans, State)
 
98
    end.
 
99
 
 
100
tr_MegacoMessage(#'MegacoMessage'{authHeader = Auth,
 
101
                                  mess       = Mess},
 
102
                 State) ->
 
103
    ?d("tr_MegacoMessage -> entry with"
 
104
       "~n   Auth:  ~p"
 
105
       "~n   Mess:  ~p"
 
106
       "~n   State: ~p", [Auth, Mess, State]),
 
107
    #'MegacoMessage'{authHeader = tr_opt_AuthenticationHeader(Auth, State),
 
108
                     mess       = tr_Message(Mess, State)}.
 
109
 
 
110
tr_opt_AuthenticationHeader(asn1_NOVALUE, _State) ->
 
111
    asn1_NOVALUE;
 
112
tr_opt_AuthenticationHeader(#'AuthenticationHeader'{secParmIndex = SPI,
 
113
                                                    seqNum       = SN,
 
114
                                                    ad           = AuthData},
 
115
                            State) ->
 
116
    #'AuthenticationHeader'{secParmIndex = tr_SecurityParmIndex(SPI, State),
 
117
                            seqNum       = tr_SequenceNum(SN, State),
 
118
                            ad           = tr_AuthData(AuthData, State)}.
 
119
 
 
120
tr_SecurityParmIndex(SPI, State) ->
 
121
    tr_HEXDIG(SPI, State, 4, 4). % BUGBUG: Mismatch between ASN.1 and ABNF
 
122
 
 
123
tr_SequenceNum(SN, State) ->
 
124
    tr_HEXDIG(SN, State, 4, 4).  % BUGBUG: Mismatch between ASN.1 and ABNF
 
125
 
 
126
tr_AuthData(AuthData, State) ->
 
127
    tr_HEXDIG(AuthData, State, 12, 32).  % BUGBUG: Mismatch between ASN.1 and ABNF
 
128
 
 
129
tr_Message(#'Message'{version     = Version,
 
130
                      mId         = MID,
 
131
                      messageBody = Body},
 
132
           State) ->
 
133
    #'Message'{version     = tr_version(Version, State),
 
134
               mId         = tr_MId(MID, State),
 
135
               messageBody = tr_Message_messageBody(Body, State)}.
 
136
 
 
137
tr_version(Version, State) ->
 
138
    tr_DIGIT(Version, State, 0, 99).
 
139
 
 
140
tr_Message_messageBody({Tag, Val}, State) ->
 
141
    Val2 = 
 
142
        case Tag of
 
143
            messageError -> tr_ErrorDescriptor(Val, State);
 
144
            transactions when list(Val) -> [tr_Transaction(T, State) || T <- Val]
 
145
        end,
 
146
    {Tag, Val2}.
 
147
 
 
148
tr_MId({Tag, Val}, State) ->
 
149
    Val2 = 
 
150
        case Tag of
 
151
            ip4Address -> tr_IP4Address(Val, State);
 
152
            ip6Address -> tr_IP6Address(Val, State);
 
153
            domainName -> tr_DomainName(Val, State);
 
154
            deviceName -> tr_PathName(Val,   State);
 
155
            mtpAddress -> tr_mtpAddress(Val, State)
 
156
        end,
 
157
    {Tag, Val2}.
 
158
 
 
159
tr_mtpAddress(MtpAddr, State) ->
 
160
    tr_OCTET_STRING(MtpAddr, State, 2, 4).  % BUGBUG: Mismatch between ASN.1 and ABNF
 
161
 
 
162
tr_DomainName(#'DomainName'{name       = Name,
 
163
                            portNumber = Port},
 
164
              State) ->
 
165
    Domain = #'DomainName'{name       = tr_STRING(Name, State), % BUGBUG: Mismatch between ASN.1 and ABNF
 
166
                           portNumber = tr_opt_portNumber(Port, State)},
 
167
    {domainName, Domain2} = resolve(mid, {domainName, Domain}, State, valid),
 
168
    Domain2.
 
169
 
 
170
tr_IP4Address(#'IP4Address'{address    = [A1, A2, A3, A4],
 
171
                            portNumber = Port},
 
172
              State) ->
 
173
    #'IP4Address'{address    = [tr_V4hex(A1, State),
 
174
                                tr_V4hex(A2, State),
 
175
                                tr_V4hex(A3, State),
 
176
                                tr_V4hex(A4, State)],
 
177
                  portNumber = tr_opt_portNumber(Port, State)}.
 
178
 
 
179
tr_V4hex(Val, State) ->
 
180
    tr_DIGIT(Val, State, 0, 255).
 
181
 
 
182
tr_IP6Address(_Val, _State) ->
 
183
    error(ipv6_not_supported). %% BUGBUG: nyi
 
184
 
 
185
tr_PathName(Path, State) ->
 
186
    %% BUGBUG: ["*"] NAME *("/" / "*"/ ALPHA / DIGIT /"_" / "$" ) 
 
187
    %% BUGBUG: ["@" pathDomainName ]
 
188
    Constraint = fun({deviceName, Item}) -> tr_STRING(Item, State, 1, 64) end,
 
189
    resolve(mid, {deviceName, Path}, State, Constraint).
 
190
 
 
191
tr_Transaction({Tag, Val}, State) ->
 
192
    Val2 = 
 
193
        case Tag of
 
194
            transactionRequest ->     tr_TransactionRequest(Val, State);
 
195
            transactionPending ->     tr_TransactionPending(Val, State);
 
196
            transactionReply ->       tr_TransactionReply(Val, State);
 
197
            transactionResponseAck -> [tr_TransactionAck(T, State) || T <- Val]
 
198
        end,
 
199
    {Tag, Val2}.
 
200
 
 
201
tr_TransactionAck(#'TransactionAck'{firstAck = First,
 
202
                                    lastAck  = Last},
 
203
                          State) ->
 
204
    #'TransactionAck'{firstAck = tr_TransactionId(First, State),
 
205
                      lastAck  = tr_opt_TransactionId(Last, State)}.
 
206
 
 
207
tr_opt_TransactionId(asn1_NOVALUE, _State) ->
 
208
    asn1_NOVALUE;
 
209
tr_opt_TransactionId(Id, State) ->
 
210
    tr_TransactionId(Id, State).
 
211
 
 
212
tr_TransactionId(Id, State) ->
 
213
    tr_UINT32(Id, State).
 
214
 
 
215
tr_TransactionRequest(#'TransactionRequest'{transactionId = Id,
 
216
                                            actions       = Actions},
 
217
                      State) when list(Actions) ->
 
218
 
 
219
    #'TransactionRequest'{transactionId = tr_TransactionId(Id, State),
 
220
                          actions       = [tr_ActionRequest(ActReq, State) || ActReq <- Actions]}.
 
221
 
 
222
tr_TransactionPending(#'TransactionPending'{transactionId = Id},
 
223
                      State) ->
 
224
    #'TransactionPending'{transactionId = tr_TransactionId(Id, State)}.
 
225
 
 
226
tr_TransactionReply(#'TransactionReply'{transactionId     = Id,
 
227
                                        immAckRequired    = ImmAck,
 
228
                                        transactionResult = TransRes},
 
229
                    State) ->
 
230
    #'TransactionReply'{transactionId     = tr_TransactionId(Id, State),
 
231
                        immAckRequired    = tr_opt_null(ImmAck, State),
 
232
                        transactionResult = tr_TransactionReply_transactionResult(TransRes, State)}.
 
233
 
 
234
tr_opt_null(asn1_NOVALUE, _State) -> asn1_NOVALUE;
 
235
tr_opt_null('NULL', _State)       -> 'NULL'.
 
236
 
 
237
tr_TransactionReply_transactionResult({Tag, Val}, State) ->
 
238
    Val2 = 
 
239
        case Tag of
 
240
            transactionError ->
 
241
                tr_ErrorDescriptor(Val, State);
 
242
            actionReplies when list(Val), Val /= [] ->
 
243
                [tr_ActionReply(ActRep, State) || ActRep <- Val]
 
244
        end,
 
245
    {Tag, Val2}.
 
246
 
 
247
tr_opt_ErrorDescriptor(asn1_NOVALUE, _State) ->
 
248
    asn1_NOVALUE;
 
249
tr_opt_ErrorDescriptor(ErrDesc, State) ->
 
250
    tr_ErrorDescriptor(ErrDesc, State).
 
251
 
 
252
tr_ErrorDescriptor(#'ErrorDescriptor'{errorCode = Code,
 
253
                                      errorText = Text},
 
254
                   State) ->
 
255
    #'ErrorDescriptor'{errorCode = tr_ErrorCode(Code, State),
 
256
                       errorText = tr_opt_ErrorText(Text, State)}.
 
257
 
 
258
tr_ErrorCode(Code, State) ->
 
259
    tr_DIGIT(Code, State, 0, 999).
 
260
 
 
261
tr_opt_ErrorText(asn1_NOVALUE, _State)  ->
 
262
    asn1_NOVALUE;
 
263
tr_opt_ErrorText(Text, State)  ->
 
264
    tr_QUOTED_STRING(Text, State).
 
265
 
 
266
tr_ContextID(CtxId, State) ->
 
267
    case CtxId of
 
268
        ?megaco_all_context_id    -> ?megaco_all_context_id;
 
269
        ?megaco_null_context_id   -> ?megaco_null_context_id;
 
270
        ?megaco_choose_context_id -> ?megaco_choose_context_id;
 
271
        Int when integer(Int)     -> tr_UINT32(Int, State)
 
272
    end.
 
273
 
 
274
tr_ActionRequest(#'ActionRequest'{contextId           = CtxId,
 
275
                                  contextRequest      = CtxReq,
 
276
                                  contextAttrAuditReq = CtxAuditReq,
 
277
                                  commandRequests     = CmdReqList},
 
278
                 State) ->
 
279
    #'ActionRequest'{contextId           = tr_ContextID(CtxId, State),
 
280
                     contextRequest      = tr_opt_ContextRequest(CtxReq, State),
 
281
                     contextAttrAuditReq = tr_opt_ContextAttrAuditRequest(CtxAuditReq, State),
 
282
                     commandRequests     = [tr_CommandRequest(CmdReq, State) || CmdReq <- CmdReqList]}.
 
283
 
 
284
tr_ActionReply(#'ActionReply'{contextId       = CtxId,
 
285
                              errorDescriptor = ErrDesc,
 
286
                              contextReply    = CtxRep,
 
287
                              commandReply    = CmdRepList},
 
288
               State) ->
 
289
    CmdRepList2 = [tr_CommandReply(CmdRep, State) || CmdRep <- CmdRepList],
 
290
    #'ActionReply'{contextId       = tr_ContextID(CtxId, State),
 
291
                   errorDescriptor = tr_opt_ErrorDescriptor(ErrDesc, State),
 
292
                   contextReply    = tr_opt_ContextRequest(CtxRep, State),
 
293
                   commandReply    = CmdRepList2}.
 
294
 
 
295
tr_opt_ContextRequest(asn1_NOVALUE, _State) ->
 
296
    asn1_NOVALUE;
 
297
tr_opt_ContextRequest(CR, State) ->
 
298
    tr_ContextRequest(CR, State).
 
299
 
 
300
tr_ContextRequest(#'ContextRequest'{priority    = Prio,
 
301
                                    emergency   = Em,
 
302
                                    topologyReq = TopReqList,
 
303
                                    iepscallind = Ind,
 
304
                                    contextProp = CtxProps,
 
305
                                    contextList = CtxList},
 
306
                  State) ->
 
307
    Prio2 = 
 
308
        case Prio of
 
309
            asn1_NOVALUE -> asn1_NOVALUE;
 
310
            _            -> tr_integer(Prio, State, 0, 15)
 
311
        end,
 
312
    Em2 = 
 
313
        case Em of
 
314
            asn1_NOVALUE -> asn1_NOVALUE;
 
315
            false        -> false;
 
316
            true         -> true
 
317
        end,
 
318
    TopReqList2 = 
 
319
        case TopReqList of
 
320
            asn1_NOVALUE -> asn1_NOVALUE;
 
321
            _            -> [tr_TopologyRequest(TopReq, State) ||
 
322
                                TopReq <- TopReqList]
 
323
        end,
 
324
    Ind2 = 
 
325
        case Ind of
 
326
            asn1_NOVALUE -> asn1_NOVALUE;
 
327
            false        -> false;
 
328
            true         -> true
 
329
        end,
 
330
    CtxProps2 = 
 
331
        case CtxProps of
 
332
            asn1_NOVALUE -> asn1_NOVALUE;
 
333
            _            -> [tr_PropertyParm(Prop, State) || Prop <- CtxProps]
 
334
        end,
 
335
    CtxList2 = 
 
336
        case CtxList of
 
337
            asn1_NOVALUE -> asn1_NOVALUE;
 
338
            _            -> [tr_ContextID(Id, State) || Id <- CtxList]
 
339
        end,
 
340
    #'ContextRequest'{priority    = Prio2,
 
341
                      emergency   = Em2,
 
342
                      topologyReq = TopReqList2,
 
343
                      iepscallind = Ind2,
 
344
                      contextProp = CtxProps2,
 
345
                      contextList = CtxList2}.
 
346
 
 
347
tr_opt_ContextAttrAuditRequest(asn1_NOVALUE, _State) ->
 
348
    asn1_NOVALUE;
 
349
tr_opt_ContextAttrAuditRequest(CAAR, State) ->
 
350
    tr_ContextAttrAuditRequest(CAAR, State).
 
351
 
 
352
tr_ContextAttrAuditRequest(#'ContextAttrAuditRequest'{topology        = Top,
 
353
                                                      emergency       = Em,
 
354
                                                      priority        = Prio,
 
355
                                                      iepscallind     = Ind,
 
356
                                                      contextPropAud  = Props,
 
357
                                                      selectpriority  = SPrio,
 
358
                                                      selectemergency = SEm,
 
359
                                                      selectiepscallind = SInd,
 
360
                                                      selectLogic     = SLog},
 
361
                               State) ->
 
362
    Top2   = tr_opt_null(Top,  State),
 
363
    Em2    = tr_opt_null(Em,   State),
 
364
    Prio2  = tr_opt_null(Prio, State),
 
365
    Ind2   = tr_opt_null(Ind,  State),
 
366
    Props2 = 
 
367
        case Props of
 
368
            asn1_NOVALUE -> 
 
369
                asn1_NOVALUE;
 
370
            _            -> 
 
371
                [tr_indAudPropertyParm(Prop, State) || Prop <- Props]
 
372
        end,
 
373
    SPrio2 = 
 
374
        case SPrio of
 
375
            asn1_NOVALUE -> asn1_NOVALUE;
 
376
            _            -> tr_integer(SPrio, State, 0, 15)
 
377
        end,
 
378
    SEm2 = 
 
379
        case SEm of
 
380
            asn1_NOVALUE -> asn1_NOVALUE;
 
381
            false        -> false;
 
382
            true         -> true
 
383
        end,
 
384
    SInd2 = 
 
385
        case SInd of
 
386
            asn1_NOVALUE -> asn1_NOVALUE;
 
387
            false        -> false;
 
388
            true         -> true
 
389
        end,
 
390
    SLog2 = 
 
391
        case SLog of
 
392
            asn1_NOVALUE -> asn1_NOVALUE;
 
393
            _            -> tr_SelectLogic(SLog, State)
 
394
        end,
 
395
    #'ContextAttrAuditRequest'{topology          = Top2,
 
396
                               emergency         = Em2, 
 
397
                               priority          = Prio2, 
 
398
                               iepscallind       = Ind2, 
 
399
                               contextPropAud    = Props2,
 
400
                               selectpriority    = SPrio2,
 
401
                               selectemergency   = SEm2,
 
402
                               selectiepscallind = SInd2,
 
403
                               selectLogic       = SLog2}.
 
404
 
 
405
tr_SelectLogic({andAUDITSelect, 'NULL'} = Val, _State) ->
 
406
    Val;
 
407
tr_SelectLogic({orAUDITSelect, 'NULL'} = Val, _State) ->
 
408
    Val.
 
409
    
 
410
tr_CommandRequest(#'CommandRequest'{command        = Cmd,
 
411
                                    optional       = Opt,
 
412
                                    wildcardReturn = Wild},
 
413
                  State) ->
 
414
    #'CommandRequest'{optional       = tr_opt_null(Opt, State),
 
415
                      wildcardReturn = tr_opt_null(Wild, State),
 
416
                      command        = tr_Command(Cmd, State)}.
 
417
 
 
418
tr_Command({Tag, Val}, State) ->
 
419
    Val2 = 
 
420
        case Tag of
 
421
            addReq ->            tr_AmmRequest(Val, State);
 
422
            moveReq ->           tr_AmmRequest(Val, State);
 
423
            modReq ->            tr_AmmRequest(Val, State);
 
424
            subtractReq ->       tr_SubtractRequest(Val, State);
 
425
            auditCapRequest ->   tr_AuditRequest(Val, State);
 
426
            auditValueRequest -> tr_AuditRequest(Val, State);
 
427
            notifyReq ->         tr_NotifyRequest(Val, State);
 
428
            serviceChangeReq ->  tr_ServiceChangeRequest(Val, State)
 
429
        end,
 
430
    {Tag, Val2}.
 
431
 
 
432
tr_CommandReply({Tag, Val}, State) ->
 
433
    Val2 = 
 
434
        case Tag of
 
435
            addReply ->           tr_AmmsReply(Val, State);
 
436
            moveReply ->          tr_AmmsReply(Val, State);
 
437
            modReply ->           tr_AmmsReply(Val, State);
 
438
            subtractReply ->      tr_AmmsReply(Val, State);
 
439
            auditCapReply ->      tr_AuditReply(Val, State);
 
440
            auditValueReply ->    tr_AuditReply(Val, State);
 
441
            notifyReply ->        tr_NotifyReply(Val, State);
 
442
            serviceChangeReply -> tr_ServiceChangeReply(Val, State)
 
443
        end,
 
444
    {Tag, Val2}.
 
445
 
 
446
tr_TopologyRequest(#'TopologyRequest'{terminationFrom            = From,
 
447
                                      terminationTo              = To,
 
448
                                      topologyDirection          = Dir,
 
449
                                      streamID                   = SID,
 
450
                                      topologyDirectionExtension = TDE},
 
451
                   State) ->
 
452
    Dir2 = 
 
453
        case Dir of
 
454
            bothway -> bothway;
 
455
            isolate -> isolate;
 
456
            oneway ->  oneway
 
457
        end,
 
458
    TDE2 = 
 
459
        case TDE of
 
460
            onewayexternal -> onewayexternal;
 
461
            onewayboth     -> onewayboth;
 
462
            asn1_NOVALUE   -> asn1_NOVALUE
 
463
        end,
 
464
    #'TopologyRequest'{terminationFrom   = tr_TerminationID(From, State),
 
465
                       terminationTo     = tr_TerminationID(To, State),
 
466
                       topologyDirection = Dir2,
 
467
                       streamID          = tr_opt_StreamID(SID, State),
 
468
                       topologyDirectionExtension = TDE2}.
 
469
 
 
470
tr_AmmRequest(#'AmmRequest'{terminationID = IdList,
 
471
                            descriptors   = DescList},
 
472
              State) ->
 
473
    #'AmmRequest'{terminationID = [tr_TerminationID(Id, State) || 
 
474
                                      Id <- IdList],
 
475
                  descriptors   = tr_ammDescriptors(DescList, [], State)}.
 
476
 
 
477
tr_ammDescriptors([], Acc, _State) ->
 
478
    lists:reverse(Acc);
 
479
tr_ammDescriptors([Desc|Descs], Acc, State) ->
 
480
    case tr_ammDescriptor(Desc, State) of
 
481
        {_, deprecated} when State#state.mode == encode ->
 
482
            error({deprecated, Desc});
 
483
        {_, deprecated} when State#state.mode == decode ->
 
484
            %% SKIP
 
485
            tr_ammDescriptors(Descs, Acc, State);
 
486
        {_, deprecated} ->
 
487
            %% SKIP
 
488
            tr_ammDescriptors(Descs, Acc, State);
 
489
        NewDesc ->
 
490
            tr_ammDescriptors(Descs, [NewDesc|Acc], State)
 
491
    end.
 
492
 
 
493
tr_ammDescriptor({Tag, Desc}, State) ->
 
494
    Desc2 = 
 
495
        case Tag of
 
496
            mediaDescriptor       -> tr_MediaDescriptor(Desc, State);
 
497
            modemDescriptor       -> tr_ModemDescriptor(Desc, State);      
 
498
            muxDescriptor         -> tr_MuxDescriptor(Desc, State);   
 
499
            eventsDescriptor      -> tr_EventsDescriptor(Desc, State);      
 
500
            eventBufferDescriptor -> tr_EventBufferDescriptor(Desc, State); 
 
501
            signalsDescriptor     -> tr_SignalsDescriptor(Desc, State);    
 
502
            digitMapDescriptor    -> tr_DigitMapDescriptor(Desc, State);    
 
503
            auditDescriptor       -> tr_AuditDescriptor(Desc, State);
 
504
            statisticsDescriptor  -> tr_StatisticsDescriptor(Desc, State)
 
505
        end,
 
506
    {Tag, Desc2}.
 
507
 
 
508
tr_AmmsReply(#'AmmsReply'{terminationID    = IdList,
 
509
                          terminationAudit = TermAudit},
 
510
             State) ->
 
511
    TermAudit2 =
 
512
        case TermAudit of
 
513
            asn1_NOVALUE -> asn1_NOVALUE;
 
514
            _            -> tr_TerminationAudit(TermAudit, State)
 
515
        end,
 
516
    #'AmmsReply'{terminationID    = [tr_TerminationID(Id, State) ||
 
517
                                        Id <- IdList],
 
518
                 terminationAudit = TermAudit2}.
 
519
 
 
520
tr_SubtractRequest(#'SubtractRequest'{terminationID   = IdList,
 
521
                                      auditDescriptor = Desc},
 
522
                   State) ->
 
523
    #'SubtractRequest'{terminationID   = [tr_TerminationID(Id, State) ||
 
524
                                             Id <- IdList],
 
525
                       auditDescriptor = tr_opt_AuditDescriptor(Desc, State)}.
 
526
 
 
527
tr_AuditRequest(#'AuditRequest'{terminationID     = Id,
 
528
                                auditDescriptor   = Desc,
 
529
                                terminationIDList = TIDList},
 
530
                State) ->
 
531
    TIDList2 = 
 
532
        case TIDList of
 
533
            asn1_NOVALUE -> asn1_NOVALUE;
 
534
            _            -> [tr_TerminationID(TID, State) || TID <- TIDList]
 
535
        end,
 
536
    #'AuditRequest'{terminationID     = tr_TerminationID(Id, State),
 
537
                    auditDescriptor   = tr_AuditDescriptor(Desc, State),
 
538
                    terminationIDList = TIDList2}.
 
539
 
 
540
%% auditReply           = (AuditValueToken / AuditCapToken ) 
 
541
%%                        ( contextTerminationAudit  / auditOther)
 
542
%% auditOther           = EQUAL TerminationID LBRKT 
 
543
%%                        terminationAudit RBRKT
 
544
%% terminationAudit     = auditReturnParameter *(COMMA auditReturnParameter) 
 
545
%% 
 
546
%% contextTerminationAudit = EQUAL CtxToken ( terminationIDList / 
 
547
%%                        LBRKT errorDescriptor RBRKT )
 
548
 
 
549
tr_AuditReply({Tag, Val}, State) ->
 
550
    Val2 =
 
551
        case Tag of
 
552
            contextAuditResult ->
 
553
                [tr_TerminationID(Id, State) || Id <- Val];
 
554
            error ->
 
555
                tr_ErrorDescriptor(Val, State);
 
556
            auditResult ->
 
557
                tr_AuditResult(Val, State);
 
558
            auditResultTermList ->
 
559
                tr_TermListAuditResult(Val, State)
 
560
        end,
 
561
    {Tag, Val2}.
 
562
 
 
563
tr_AuditResult(#'AuditResult'{terminationID          = Id,
 
564
                              terminationAuditResult = AuditRes},
 
565
              State) ->
 
566
    #'AuditResult'{terminationID          = tr_TerminationID(Id, State),
 
567
                   terminationAuditResult = tr_TerminationAudit(AuditRes, State)}.
 
568
 
 
569
tr_TermListAuditResult(
 
570
  #'TermListAuditResult'{terminationIDList      = TIDList,
 
571
                         terminationAuditResult = TAR},
 
572
  State) ->
 
573
    TIDList2 = [tr_TerminationID(TID, State) || TID <- TIDList],
 
574
    TAR2     = tr_TerminationAudit(TAR, State), 
 
575
    #'TermListAuditResult'{terminationIDList      = TIDList2,
 
576
                           terminationAuditResult = TAR2}.
 
577
 
 
578
 
 
579
tr_opt_AuditDescriptor(asn1_NOVALUE, _State) ->
 
580
    asn1_NOVALUE;
 
581
tr_opt_AuditDescriptor(Desc, State) ->
 
582
    tr_AuditDescriptor(Desc, State).
 
583
 
 
584
%% BUGBUG BUGBUG BUGBUG 
 
585
%% With this construction it is possible to have both auditToken
 
586
%% and auditPropertyToken, but it is actually valid?
 
587
tr_AuditDescriptor(#'AuditDescriptor'{auditToken         = Tokens,
 
588
                                      auditPropertyToken = APTs},
 
589
                   State) ->
 
590
    Tokens2 = 
 
591
        case Tokens of
 
592
            asn1_NOVALUE -> asn1_NOVALUE;
 
593
            _            -> [tr_auditItem(Token, State) || Token <- Tokens]
 
594
        end,
 
595
    %% v2
 
596
    APTs2 = 
 
597
        case APTs of
 
598
            asn1_NOVALUE -> 
 
599
                asn1_NOVALUE;
 
600
            _ -> 
 
601
                [tr_indAuditParameter(APT, State) || APT <- APTs]
 
602
        end,
 
603
    #'AuditDescriptor'{auditToken         = Tokens2,
 
604
                       auditPropertyToken = APTs2}.  
 
605
 
 
606
tr_auditItem(Token, _State) ->
 
607
    case Token of
 
608
        muxToken            -> muxToken;
 
609
        modemToken          -> modemToken;
 
610
        mediaToken          -> mediaToken;
 
611
        eventsToken         -> eventsToken;
 
612
        signalsToken        -> signalsToken;
 
613
        digitMapToken       -> digitMapToken;
 
614
        statsToken          -> statsToken;
 
615
        observedEventsToken -> observedEventsToken;
 
616
        packagesToken       -> packagesToken;
 
617
        eventBufferToken    -> eventBufferToken
 
618
    end.
 
619
 
 
620
%% --- v2 begin ---
 
621
 
 
622
tr_indAuditParameter({Tag, Val}, State) ->
 
623
    Val2 = 
 
624
        case Tag of
 
625
            indAudMediaDescriptor       -> 
 
626
                tr_indAudMediaDescriptor(Val, State);
 
627
            indAudEventsDescriptor      -> 
 
628
                tr_indAudEventsDescriptor(Val, State);
 
629
            indAudSignalsDescriptor     -> 
 
630
                tr_indAudSignalsDescriptor(Val, State);
 
631
            indAudDigitMapDescriptor    -> 
 
632
                tr_indAudDigitMapDescriptor(Val, State);
 
633
            indAudEventBufferDescriptor -> 
 
634
                tr_indAudEventBufferDescriptor(Val, State);
 
635
            indAudStatisticsDescriptor  -> 
 
636
                tr_indAudStatisticsDescriptor(Val, State);
 
637
            indAudPackagesDescriptor    -> 
 
638
                tr_indAudPackagesDescriptor(Val, State)
 
639
        end,
 
640
    {Tag, Val2}.
 
641
 
 
642
 
 
643
%% -
 
644
 
 
645
tr_indAudMediaDescriptor(#'IndAudMediaDescriptor'{termStateDescr = TSD,
 
646
                                                  streams        = S}, 
 
647
                         State) ->
 
648
    TSD2 = 
 
649
        case TSD of
 
650
            asn1_NOVALUE -> 
 
651
                asn1_NOVALUE;
 
652
            _ -> 
 
653
                tr_indAudTerminationStateDescriptor(TSD, State)
 
654
        end,
 
655
    S2 = 
 
656
        case S of
 
657
            asn1_NOVALUE -> 
 
658
                asn1_NOVALUE;
 
659
            {oneStream, OS} ->
 
660
                {oneStream, tr_indAudStreamParms(OS, State)};
 
661
            {multiStream, MS} ->
 
662
                MS2 = [tr_indAudStreamDescriptor(MS1, State) || MS1 <- MS],
 
663
                {multiStream, MS2}
 
664
        end,
 
665
    #'IndAudMediaDescriptor'{termStateDescr = TSD2,
 
666
                             streams        = S2}.
 
667
 
 
668
tr_indAudTerminationStateDescriptor(Val, State) 
 
669
  when record(Val, 'IndAudTerminationStateDescriptor') ->
 
670
    #'IndAudTerminationStateDescriptor'{propertyParms      = Parms,
 
671
                                        eventBufferControl = EBC,
 
672
                                        serviceState       = SS,
 
673
                                        serviceStateSel    = SSS} = Val,
 
674
    Parms2 = [tr_indAudPropertyParm(Parm, State) || Parm <- Parms],
 
675
    EBC2   = tr_opt_null(EBC, State),
 
676
    SS2    = tr_opt_null(SS, State),
 
677
    SSS2   = tr_opt_ServiceState(SSS, State),
 
678
    #'IndAudTerminationStateDescriptor'{propertyParms      = Parms2, 
 
679
                                        eventBufferControl = EBC2,
 
680
                                        serviceState       = SS2,
 
681
                                        serviceStateSel    = SSS2}.
 
682
 
 
683
    
 
684
tr_indAudStreamParms(#'IndAudStreamParms'{localControlDescriptor = LCD, 
 
685
                                          localDescriptor        = LD, 
 
686
                                          remoteDescriptor       = RD,
 
687
                                          statisticsDescriptor   = SD}, 
 
688
                     State) ->
 
689
    LCD2 = 
 
690
        case LCD of
 
691
            asn1_NOVALUE ->
 
692
                asn1_NOVALUE;
 
693
            _ ->
 
694
                tr_indAudLocalControlDescriptor(LCD, State)
 
695
        end,
 
696
    LD2 = 
 
697
        case LD of
 
698
            asn1_NOVALUE ->
 
699
                asn1_NOVALUE;
 
700
            _ ->
 
701
                tr_indAudLocalRemoteDescriptor(LD, State)
 
702
        end,
 
703
    RD2 = 
 
704
        case RD of
 
705
            asn1_NOVALUE ->
 
706
                asn1_NOVALUE;
 
707
            _ ->
 
708
                tr_indAudLocalRemoteDescriptor(RD, State)
 
709
        end,
 
710
    SD2 = 
 
711
        case SD of
 
712
            asn1_NOVALUE ->
 
713
                asn1_NOVALUE;
 
714
            _ ->
 
715
                tr_indAudStatisticsDescriptor(SD, State)
 
716
        end,
 
717
    #'IndAudStreamParms'{localControlDescriptor = LCD2, 
 
718
                         localDescriptor        = LD2, 
 
719
                         remoteDescriptor       = RD2,
 
720
                         statisticsDescriptor   = SD2}.
 
721
    
 
722
tr_indAudLocalControlDescriptor(Val, State) 
 
723
  when record(Val, 'IndAudLocalControlDescriptor') ->
 
724
    #'IndAudLocalControlDescriptor'{streamMode    = M,
 
725
                                    reserveValue  = V,
 
726
                                    reserveGroup  = G,
 
727
                                    propertyParms = P,
 
728
                                    streamModeSel = SMS} = Val,
 
729
    M2   = tr_opt_null(M, State),
 
730
    V2   = tr_opt_null(V, State),
 
731
    G2   = tr_opt_null(G, State),
 
732
    P2   = tr_indAudLocalControlDescriptor_propertyParms(P, State),
 
733
    SMS2 = tr_opt_StreamMode(SMS, State),
 
734
    #'IndAudLocalControlDescriptor'{streamMode    = M2,
 
735
                                    reserveValue  = V2,
 
736
                                    reserveGroup  = G2,
 
737
                                    propertyParms = P2,
 
738
                                    streamModeSel = SMS2}.
 
739
 
 
740
tr_indAudLocalControlDescriptor_propertyParms(Parms, State) 
 
741
  when list(Parms), length(Parms) > 0 ->
 
742
    [tr_indAudPropertyParm(Parm, State) || Parm <- Parms];
 
743
tr_indAudLocalControlDescriptor_propertyParms(asn1_NOVALUE, _State) ->
 
744
    asn1_NOVALUE.
 
745
 
 
746
tr_indAudLocalRemoteDescriptor(#'IndAudLocalRemoteDescriptor'{propGroupID = ID,
 
747
                                                              propGrps = Grps},
 
748
                               State) ->
 
749
    #'IndAudLocalRemoteDescriptor'{propGroupID = tr_opt_UINT16(ID, State),
 
750
                                   propGrps = tr_indAudPropertyGroup(Grps, 
 
751
                                                                     State)}.
 
752
 
 
753
tr_indAudPropertyGroup(Grps, State) when list(Grps) ->
 
754
    [tr_indAudPropertyParm(Parm, State) || Parm <- Grps].
 
755
 
 
756
tr_indAudPropertyParm(#'IndAudPropertyParm'{name          = Name0,
 
757
                                            propertyParms = Prop0}, State) ->
 
758
    Constraint = fun(Item) -> tr_PkgdName(Item, State) end,
 
759
    Name = resolve(property, Name0, State, Constraint),
 
760
    Prop = 
 
761
        case Prop0 of
 
762
            asn1_NOVALUE -> asn1_NOVALUE;
 
763
            _            -> tr_PropertyParm(Prop0, State)
 
764
        end,
 
765
    #'IndAudPropertyParm'{name          = Name,
 
766
                          propertyParms = Prop}.
 
767
 
 
768
 
 
769
tr_indAudStreamDescriptor(#'IndAudStreamDescriptor'{streamID = ID,
 
770
                                                    streamParms = Parms},
 
771
                          State) ->
 
772
    #'IndAudStreamDescriptor'{streamID    = tr_StreamID(ID, State),
 
773
                              streamParms = tr_indAudStreamParms(Parms, 
 
774
                                                                 State)}.
 
775
 
 
776
 
 
777
%% -
 
778
 
 
779
tr_indAudEventsDescriptor(#'IndAudEventsDescriptor'{requestID = RID,
 
780
                                                    pkgdName  = Name0,
 
781
                                                    streamID  = SID},
 
782
                          State) ->
 
783
    Constraint = fun(Item) -> tr_PkgdName(Item, State) end,
 
784
    Name = resolve(event, Name0, State, Constraint),
 
785
    #'IndAudEventsDescriptor'{requestID = tr_opt_RequestID(RID, State),
 
786
                              pkgdName  = Name, 
 
787
                              streamID  = tr_opt_StreamID(SID, State)}.
 
788
 
 
789
 
 
790
%% -
 
791
 
 
792
tr_indAudSignalsDescriptor({Tag, Val}, State) ->
 
793
    case Tag of
 
794
        signal ->
 
795
            {signal, tr_indAudSignal(Val, State)};
 
796
        seqSigList ->
 
797
            {seqSigList, tr_indAudSeqSigList(Val, State)}
 
798
    end.
 
799
 
 
800
tr_opt_indAudSignal(asn1_NOVALUE, _State) ->
 
801
    asn1_NOVALUE;
 
802
tr_opt_indAudSignal(Val, State) ->
 
803
    tr_indAudSignal(Val, State).
 
804
 
 
805
tr_indAudSignal(#'IndAudSignal'{signalName      = Name0,
 
806
                                streamID        = SID,
 
807
                                signalRequestID = RID}, State) ->
 
808
    Constraint = fun(Item) -> tr_PkgdName(Item, State) end,
 
809
    Name = resolve(signal, Name0, State, Constraint),
 
810
    #'IndAudSignal'{signalName      = Name, 
 
811
                    streamID        = tr_opt_StreamID(SID, State),
 
812
                    signalRequestID = tr_opt_RequestID(RID, State)}.
 
813
 
 
814
tr_indAudSeqSigList(#'IndAudSeqSigList'{id = ID,
 
815
                                        signalList = SigList}, State) ->
 
816
    #'IndAudSeqSigList'{id = tr_integer(ID, State, 0, 65535),
 
817
                        signalList = tr_opt_indAudSignal(SigList, State)}.
 
818
 
 
819
%% -
 
820
 
 
821
tr_indAudDigitMapDescriptor(#'IndAudDigitMapDescriptor'{digitMapName = Name},
 
822
                            State) ->
 
823
    #'IndAudDigitMapDescriptor'{digitMapName = 
 
824
                                tr_opt_DigitMapName(Name, State)}.
 
825
 
 
826
 
 
827
%% -
 
828
 
 
829
tr_indAudEventBufferDescriptor(#'IndAudEventBufferDescriptor'{eventName = N,
 
830
                                                              streamID  = SID},
 
831
                               State) ->
 
832
    ?d("tr_indAudEventBufferDescriptor -> entry with"
 
833
       "~n   N:   ~p"
 
834
       "~n   SID: ~p", [N, SID]),
 
835
    Constraint = fun(Item) -> tr_PkgdName(Item, State) end,
 
836
    Name = resolve(event, N, State, Constraint),
 
837
    ?d("tr_indAudEventBufferDescriptor -> entry with"
 
838
       "~n   Name: ~p", [Name]),
 
839
    #'IndAudEventBufferDescriptor'{eventName = Name,
 
840
                                   streamID  = tr_opt_StreamID(SID, State)}.
 
841
 
 
842
%% -
 
843
 
 
844
tr_indAudStatisticsDescriptor(#'IndAudStatisticsDescriptor'{statName = N},
 
845
                              State) ->
 
846
    ?d("tr_indAudEventBufferDescriptor -> entry with"
 
847
       "~n   N:   ~p", [N]),
 
848
    Constraint = fun(Item) -> tr_PkgdName(Item, State) end,
 
849
    Name = resolve(statistics, N, State, Constraint),
 
850
    #'IndAudStatisticsDescriptor'{statName = Name}.
 
851
 
 
852
 
 
853
%% -
 
854
 
 
855
tr_indAudPackagesDescriptor(#'IndAudPackagesDescriptor'{packageName    = N,
 
856
                                                        packageVersion = V}, 
 
857
                            State) ->
 
858
    ?d("tr_indAudPackagesDescriptor -> entry with"
 
859
       "~n   N: ~p"
 
860
       "~n   V: ~p", [N, V]),
 
861
    Constraint = fun(Item) -> tr_Name(Item, State) end,
 
862
    Name = resolve(package, N, State, Constraint),
 
863
    ?d("tr_indAudPackagesDescriptor -> entry with"
 
864
       "~n   Name: ~p", [Name]),
 
865
    #'IndAudPackagesDescriptor'{packageName = Name, 
 
866
                                packageVersion = tr_integer(V, State, 0, 99)}.
 
867
 
 
868
%% -- v2 end --
 
869
 
 
870
 
 
871
tr_TerminationAudit(ParmList, State) when list(ParmList) ->
 
872
    do_tr_TerminationAudit(ParmList, [], State).
 
873
 
 
874
do_tr_TerminationAudit([], Acc, _State) ->
 
875
    lists:reverse(Acc);
 
876
do_tr_TerminationAudit([Parm|ParmList], Acc, State) ->
 
877
    case tr_AuditReturnParameter(Parm, State) of
 
878
        {_, deprecated} when State#state.mode == encode ->
 
879
            error({deprecated, Parm});
 
880
        {_, deprecated} when State#state.mode == decode ->
 
881
            %% SKIP
 
882
            do_tr_TerminationAudit(ParmList, Acc, State);
 
883
        {_, deprecated} ->
 
884
            %% SKIP
 
885
            do_tr_TerminationAudit(ParmList, Acc, State);
 
886
        NewParm ->
 
887
            do_tr_TerminationAudit(ParmList, [NewParm|Acc], State)
 
888
    end.
 
889
 
 
890
tr_AuditReturnParameter({Tag, Val}, State) ->
 
891
    Val2 = 
 
892
        case Tag of
 
893
            errorDescriptor ->
 
894
                tr_ErrorDescriptor(Val, State);
 
895
            mediaDescriptor ->
 
896
                tr_MediaDescriptor(Val, State);
 
897
            modemDescriptor ->
 
898
                tr_ModemDescriptor(Val, State);
 
899
            muxDescriptor ->
 
900
                tr_MuxDescriptor(Val, State);
 
901
            eventsDescriptor ->
 
902
                tr_EventsDescriptor(Val, State);
 
903
            eventBufferDescriptor ->
 
904
                tr_EventBufferDescriptor(Val, State);
 
905
            signalsDescriptor ->
 
906
                tr_SignalsDescriptor(Val, State);
 
907
            digitMapDescriptor ->
 
908
                tr_DigitMapDescriptor(Val, State);
 
909
            observedEventsDescriptor ->
 
910
                tr_ObservedEventsDescriptor(Val, State);
 
911
            statisticsDescriptor ->
 
912
                tr_StatisticsDescriptor(Val, State);
 
913
            packagesDescriptor ->
 
914
                tr_PackagesDescriptor(Val, State);
 
915
            emptyDescriptors ->
 
916
                tr_EmptyDescriptors(Val, State)
 
917
        end,
 
918
    {Tag, Val2}.
 
919
 
 
920
tr_EmptyDescriptors(#'AuditDescriptor'{auditToken = Tokens},
 
921
                    State) ->
 
922
    Tokens2 = 
 
923
        case Tokens of
 
924
            asn1_NOVALUE -> asn1_NOVALUE;
 
925
            _            -> [tr_auditItem(Token, State) || Token <- Tokens]
 
926
        end,
 
927
    #'AuditDescriptor'{auditToken = Tokens2}.
 
928
 
 
929
tr_NotifyRequest(#'NotifyRequest'{terminationID            = IdList,
 
930
                                  observedEventsDescriptor = ObsDesc,
 
931
                                  errorDescriptor          = ErrDesc},
 
932
                 State) ->
 
933
    %% BUGBUG: Mismatch between ASN.1 and ABNF
 
934
    %% BUGBUG: The following ought to be a 'choice'
 
935
    #'NotifyRequest'{terminationID            = [tr_TerminationID(Id, State) ||
 
936
                                                    Id <- IdList],
 
937
                     observedEventsDescriptor = tr_ObservedEventsDescriptor(ObsDesc, State),
 
938
                     errorDescriptor          = tr_opt_ErrorDescriptor(ErrDesc, State)}.
 
939
 
 
940
tr_NotifyReply(#'NotifyReply'{terminationID   = IdList,
 
941
                              errorDescriptor = ErrDesc},
 
942
               State) ->
 
943
    #'NotifyReply'{terminationID   = [tr_TerminationID(Id, State) || Id <- IdList],
 
944
                   errorDescriptor = tr_opt_ErrorDescriptor(ErrDesc, State)}.
 
945
 
 
946
tr_ObservedEventsDescriptor(#'ObservedEventsDescriptor'{requestId        = Id,
 
947
                                                        observedEventLst = Events},
 
948
                            State) when list (Events) ->
 
949
    #'ObservedEventsDescriptor'{requestId        = tr_RequestID(Id, State),
 
950
                                observedEventLst = [tr_ObservedEvent(E, State) || E <- Events]}.
 
951
 
 
952
%% ;time per event, because it might be buffered
 
953
%% observedEvent        = [ TimeStamp LWSP COLON] LWSP 
 
954
%%                        pkgdName [ LBRKT observedEventParameter
 
955
%%                        *(COMMA observedEventParameter) RBRKT ]
 
956
%% 
 
957
%% ;at-most-once eventStream, every eventParameterName at most once
 
958
%% observedEventParameter = eventStream / eventOther
 
959
 
 
960
tr_ObservedEvent(#'ObservedEvent'{eventName    = Name,
 
961
                                  streamID     = Id,
 
962
                                  eventParList = Parms,
 
963
                                  timeNotation = Time},
 
964
                 State) ->
 
965
    #'ObservedEvent'{eventName    = tr_EventName(Name, State),
 
966
                     streamID     = tr_opt_StreamID(Id, State),
 
967
                     eventParList = [tr_EventParameter(P, Name, State) || P <- Parms],
 
968
                     timeNotation = tr_opt_TimeNotation(Time, State)}.
 
969
 
 
970
tr_EventName(Name, State) ->
 
971
    Constraint = fun(Item) -> tr_PkgdName(Item, State) end,
 
972
    resolve(event, Name, State, Constraint).
 
973
 
 
974
tr_EventParameter(#'EventParameter'{eventParameterName = ParName,
 
975
                                    value              = Value,
 
976
                                    extraInfo          = Extra},
 
977
                  EventName,
 
978
                  State) ->
 
979
    %% BUGBUG: event parameter name
 
980
    Constraint = fun(Item) -> tr_Name(Item, State) end,
 
981
    N = resolve({event_parameter, EventName}, ParName, State, Constraint),
 
982
    #'EventParameter'{eventParameterName = N,
 
983
                      value              = tr_Value(Value, State),
 
984
                      extraInfo          = tr_opt_extraInfo(Extra, State)}.
 
985
 
 
986
tr_ServiceChangeRequest(#'ServiceChangeRequest'{terminationID      = IdList,
 
987
                                                serviceChangeParms = Parms},
 
988
                        State) ->
 
989
    #'ServiceChangeRequest'{terminationID      = [tr_TerminationID(Id, State) || Id <- IdList],
 
990
                            serviceChangeParms = tr_ServiceChangeParm(Parms, State)}.
 
991
 
 
992
%% serviceChangeReply   = ServiceChangeToken EQUAL TerminationID
 
993
%%                        [LBRKT (errorDescriptor / 
 
994
%%                        serviceChangeReplyDescriptor) RBRKT]
 
995
%% serviceChangeReplyDescriptor = ServicesToken LBRKT
 
996
%%                        servChgReplyParm *(COMMA servChgReplyParm) RBRKT
 
997
%% 
 
998
%% ;at-most-once. Version is REQUIRED on first ServiceChange response
 
999
%% servChgReplyParm     = (serviceChangeAddress / serviceChangeMgcId /
 
1000
%%                        serviceChangeProfile / serviceChangeVersion )
 
1001
tr_ServiceChangeReply(#'ServiceChangeReply'{terminationID       = IdList,
 
1002
                                            serviceChangeResult = Res},
 
1003
                      State) ->
 
1004
    #'ServiceChangeReply'{terminationID       = [tr_TerminationID(Id, State) || Id <- IdList],
 
1005
                          serviceChangeResult = tr_ServiceChangeResult(Res, State)}.
 
1006
 
 
1007
tr_ServiceChangeResult({Tag, Val}, State) ->
 
1008
    Val2 = 
 
1009
        case Tag of
 
1010
            errorDescriptor       -> tr_ErrorDescriptor(Val, State);
 
1011
            serviceChangeResParms -> tr_ServiceChangeResParm(Val, State)
 
1012
        end,
 
1013
    {Tag, Val2}.
 
1014
 
 
1015
%% TerminationID        = "ROOT" / pathNAME / "$" / "*"
 
1016
%% ; Total length of pathNAME must not exceed 64 chars.
 
1017
%% pathNAME             = ["*"] NAME *("/" / "*"/ ALPHA / DIGIT /"_" / "$" ) 
 
1018
%%                        ["@" pathDomainName ]
 
1019
 
 
1020
tr_TerminationID(TermId, State) when State#state.mode /= verify ->
 
1021
    resolve(term_id, TermId, State, valid);
 
1022
tr_TerminationID(#'TerminationID'{wildcard = Wild,
 
1023
                                  id       = Id},
 
1024
                 _State) ->
 
1025
    #'TerminationID'{wildcard = Wild,
 
1026
                     id       = Id};
 
1027
tr_TerminationID(#megaco_term_id{contains_wildcards = IsWild,
 
1028
                                 id                 = Id},
 
1029
                 State) ->
 
1030
    #megaco_term_id{contains_wildcards = tr_bool(IsWild, State),
 
1031
                    id                 = [tr_term_id_component(Sub, State) || Sub <- Id]}.
 
1032
 
 
1033
tr_opt_bool(asn1_NOVALUE, _State) -> asn1_NOVALUE;
 
1034
tr_opt_bool(Bool, State)         -> tr_bool(Bool, State).
 
1035
 
 
1036
tr_bool(true, _State)  -> true;
 
1037
tr_bool(false, _State) -> false.
 
1038
 
 
1039
tr_term_id_component(Sub, _State) ->
 
1040
    case Sub of
 
1041
        all    -> all;
 
1042
        choose -> choose;
 
1043
        Char when integer(Char) -> Char
 
1044
    end.
 
1045
 
 
1046
%% mediaDescriptor      = MediaToken LBRKT mediaParm *(COMMA mediaParm) RBRKT
 
1047
%% ; at-most-once per item
 
1048
%% ; and either streamParm or streamDescriptor but not both
 
1049
%% mediaParm            = (streamParm / streamDescriptor / 
 
1050
%%                         terminationStateDescriptor)
 
1051
%% ; at-most-once
 
1052
%% streamParm           = ( localDescriptor / remoteDescriptor / 
 
1053
%%                         localControlDescriptor )
 
1054
%% streamDescriptor     = StreamToken EQUAL StreamID LBRKT streamParm 
 
1055
%%                        *(COMMA streamParm) RBRKT
 
1056
tr_MediaDescriptor(#'MediaDescriptor'{termStateDescr = TermState,
 
1057
                                      streams        = Streams},
 
1058
                   State) ->
 
1059
    #'MediaDescriptor'{termStateDescr = tr_opt_TerminationStateDescriptor(TermState, State),
 
1060
                       streams        = tr_opt_streams(Streams, State)}.
 
1061
 
 
1062
tr_opt_streams(asn1_NOVALUE, _State) ->
 
1063
    asn1_NOVALUE;
 
1064
tr_opt_streams({Tag, Val}, State) ->
 
1065
    Val2 = 
 
1066
        case Tag of
 
1067
            oneStream   -> tr_StreamParms(Val, State);
 
1068
            multiStream -> [tr_StreamDescriptor(SD, State) || SD <- Val]
 
1069
        end,
 
1070
    {Tag, Val2}.
 
1071
 
 
1072
tr_StreamParms(#'StreamParms'{localControlDescriptor = LCD,
 
1073
                              localDescriptor        = LD,
 
1074
                              remoteDescriptor       = RD,
 
1075
                              statisticsDescriptor   = SD},
 
1076
               State) ->
 
1077
    LCD2 = tr_opt_LocalControlDescriptor(LCD, State),
 
1078
    LD2  = tr_opt_LocalRemoteDescriptor(LD,   State),
 
1079
    RD2  = tr_opt_LocalRemoteDescriptor(RD,   State),
 
1080
    SD2  = tr_opt_StatisticsDescriptor(SD,    State),
 
1081
    #'StreamParms'{localControlDescriptor = LCD2,
 
1082
                   localDescriptor        = LD2,
 
1083
                   remoteDescriptor       = RD2,
 
1084
                   statisticsDescriptor   = SD2}.
 
1085
 
 
1086
tr_StreamDescriptor(#'StreamDescriptor'{streamID    = Id,
 
1087
                                        streamParms = Parms},
 
1088
                    State) ->
 
1089
    #'StreamDescriptor'{streamID    = tr_StreamID(Id, State),
 
1090
                        streamParms = tr_StreamParms(Parms, State)}.
 
1091
 
 
1092
%% localControlDescriptor = LocalControlToken LBRKT localParm 
 
1093
%%                          *(COMMA localParm) RBRKT
 
1094
%% 
 
1095
%% ; at-most-once per item
 
1096
%% localParm            = ( streamMode / propertyParm /
 
1097
%%                          reservedValueMode  / reservedGroupMode ) 
 
1098
%% reservedValueMode       = ReservedValueToken EQUAL ( "ON" / "OFF" ) 
 
1099
%% reservedGroupMode       = ReservedGroupToken EQUAL ( "ON" / "OFF" ) 
 
1100
%% 
 
1101
%% reservedMode      = ReservedToken EQUAL ( "ON" / "OFF" )
 
1102
%% 
 
1103
%% streamMode           = ModeToken EQUAL streamModes
 
1104
tr_opt_LocalControlDescriptor(asn1_NOVALUE, _State) ->
 
1105
    asn1_NOVALUE;
 
1106
tr_opt_LocalControlDescriptor(#'LocalControlDescriptor'{streamMode    = Mode,
 
1107
                                                        reserveGroup  = Group,
 
1108
                                                        reserveValue  = Value,
 
1109
                                                        propertyParms = Props},
 
1110
                              State) ->
 
1111
    #'LocalControlDescriptor'{streamMode    = tr_opt_StreamMode(Mode, State),
 
1112
                              reserveGroup  = tr_opt_bool(Group, State),
 
1113
                              reserveValue  = tr_opt_bool(Value, State),
 
1114
                              propertyParms = [tr_PropertyParm(P, State) || P <- Props]}.
 
1115
 
 
1116
tr_opt_StreamMode(Mode, _State) ->
 
1117
    case Mode of
 
1118
        asn1_NOVALUE -> asn1_NOVALUE;
 
1119
        sendOnly     -> sendOnly;
 
1120
        recvOnly     -> recvOnly;
 
1121
        sendRecv     -> sendRecv;
 
1122
        inactive     -> inactive;
 
1123
        loopBack     -> loopBack
 
1124
    end.
 
1125
 
 
1126
tr_Name(Name, State) ->
 
1127
    %% BUGBUG: transform
 
1128
    %% BUGBUG: NAME = ALPHA *63(ALPHA / DIGIT / "_" )
 
1129
    tr_STRING(Name, State, 2, 2).
 
1130
 
 
1131
tr_PkgdName(Name, State) ->
 
1132
    %% BUGBUG: transform
 
1133
    %% BUGBUG:  pkgdName =  (NAME / "*")  SLASH  (ItemID / "*" )
 
1134
    tr_OCTET_STRING(Name, State, 4, 4).
 
1135
 
 
1136
%% When text encoding the protocol, the descriptors consist of session
 
1137
%% descriptions as defined in SDP (RFC2327), except that the "s=", "t="
 
1138
%% and "o=" lines are optional. When multiple session descriptions are
 
1139
%% provided in one descriptor, the "v=" lines are required as delimiters;
 
1140
%% otherwise they are optional.  Implementations shall accept session
 
1141
%% descriptions that are fully conformant to RFC2327. When binary
 
1142
%% encoding the protocol the descriptor consists of groups of properties
 
1143
%% (tag-value pairs) as specified in Annex C.  Each such group may
 
1144
%% contain the parameters of a session description.
 
1145
tr_opt_LocalRemoteDescriptor(asn1_NOVALUE, _State) ->
 
1146
    asn1_NOVALUE;
 
1147
tr_opt_LocalRemoteDescriptor(#'LocalRemoteDescriptor'{propGrps = Groups},
 
1148
                             State) ->
 
1149
    #'LocalRemoteDescriptor'{propGrps = [tr_PropertyGroup(G, State) || G <- Groups]}.
 
1150
 
 
1151
tr_PropertyGroup(Props, State) ->
 
1152
    [tr_PropertyGroupParm(P, State) || P <- Props].
 
1153
 
 
1154
tr_PropertyGroupParm(#'PropertyParm'{name  = Name,
 
1155
                                     value = Value},
 
1156
                     State) ->
 
1157
    Constraint = fun(Item) -> tr_PkgdName(Item, State) end,
 
1158
    #'PropertyParm'{name  = resolve(property, Name, State, Constraint),
 
1159
                    value = tr_OCTET_STRING(Value, State, 0, infinity)}.
 
1160
 
 
1161
tr_PropertyParm(#'PropertyParm'{name      = Name,
 
1162
                                value     = Value,
 
1163
                                extraInfo = Extra},
 
1164
                State) ->
 
1165
    Constraint = fun(Item) -> tr_PkgdName(Item, State) end,
 
1166
    #'PropertyParm'{name      = resolve(property, Name, State, Constraint),
 
1167
                    value     = tr_Value(Value, State),
 
1168
                    extraInfo = tr_opt_extraInfo(Extra, State)}.
 
1169
 
 
1170
tr_opt_extraInfo(asn1_NOVALUE, _State) ->
 
1171
    asn1_NOVALUE;
 
1172
tr_opt_extraInfo({relation, Rel}, _State) ->
 
1173
    Rel2 = 
 
1174
        case Rel of
 
1175
            greaterThan -> greaterThan;
 
1176
            smallerThan -> smallerThan;
 
1177
            unequalTo   -> unequalTo
 
1178
        end,
 
1179
    {relation, Rel2};
 
1180
tr_opt_extraInfo({range, Range}, State) ->
 
1181
    Range2 = tr_bool(Range, State),
 
1182
    {range, Range2};
 
1183
tr_opt_extraInfo({sublist, Sub}, State) ->
 
1184
    Sub2 = tr_bool(Sub, State),
 
1185
    {sublist, Sub2}.
 
1186
 
 
1187
tr_opt_TerminationStateDescriptor(asn1_NOVALUE, _State) ->
 
1188
    asn1_NOVALUE;
 
1189
tr_opt_TerminationStateDescriptor(#'TerminationStateDescriptor'{propertyParms      = Props,
 
1190
                                                                eventBufferControl = Control,
 
1191
                                                                serviceState       = Service},
 
1192
                                  State) ->
 
1193
    #'TerminationStateDescriptor'{propertyParms      = [tr_PropertyParm(P, State) || P <- Props],
 
1194
                                  eventBufferControl = tr_opt_EventBufferControl(Control, State),
 
1195
                                  serviceState       = tr_opt_ServiceState(Service, State)}.
 
1196
 
 
1197
tr_opt_EventBufferControl(Control, _State) ->
 
1198
    case Control of
 
1199
        asn1_NOVALUE -> asn1_NOVALUE;
 
1200
        off          -> off;
 
1201
        lockStep     -> lockStep
 
1202
    end.
 
1203
 
 
1204
tr_opt_ServiceState(Service, _State) ->
 
1205
    case Service of
 
1206
        asn1_NOVALUE -> asn1_NOVALUE;
 
1207
        test         -> test;
 
1208
        outOfSvc     -> outOfSvc;
 
1209
        inSvc        -> inSvc
 
1210
    end.
 
1211
 
 
1212
tr_MuxDescriptor(#'MuxDescriptor'{muxType  = Type,
 
1213
                                  termList = IdList},
 
1214
                 State) ->
 
1215
    #'MuxDescriptor'{muxType  = tr_MuxType(Type, State),
 
1216
                     termList = [tr_TerminationID(Id, State) || Id <- IdList]}.
 
1217
 
 
1218
tr_MuxType(Type, _State) ->
 
1219
    case Type of
 
1220
        h221 -> h221;
 
1221
        h223 -> h223;
 
1222
        h226 -> h226;
 
1223
        v76  -> v76
 
1224
    end.
 
1225
 
 
1226
tr_opt_StreamID(asn1_NOVALUE, _State) ->
 
1227
    asn1_NOVALUE;
 
1228
tr_opt_StreamID(Id, State) ->
 
1229
    tr_StreamID(Id, State).
 
1230
 
 
1231
tr_StreamID(Id, State) ->
 
1232
    tr_UINT16(Id, State).
 
1233
 
 
1234
tr_EventsDescriptor(#'EventsDescriptor'{requestID = Id,
 
1235
                                        eventList = Events},
 
1236
                    State) ->
 
1237
    #'EventsDescriptor'{requestID = tr_opt_RequestID(Id, State),
 
1238
                        eventList = [tr_RequestedEvent(E, State) || E <- Events]}.
 
1239
 
 
1240
tr_RequestedEvent(#'RequestedEvent'{pkgdName    = Name,
 
1241
                                    streamID    = Id,
 
1242
                                    evParList   = Parms,
 
1243
                                    eventAction = Actions},
 
1244
                  State)  ->
 
1245
    Constraint = fun(Item) -> tr_PkgdName(Item, State) end,
 
1246
    #'RequestedEvent'{pkgdName    = resolve(event, Name, State, Constraint),
 
1247
                      streamID    = tr_opt_StreamID(Id, State),
 
1248
                      eventAction = tr_opt_RequestedActions(Actions, State),
 
1249
                      evParList   = [tr_EventParameter(P, Name, State) || P <- Parms]}.
 
1250
 
 
1251
tr_RegulatedEmbeddedDescriptor(
 
1252
  #'RegulatedEmbeddedDescriptor'{secondEvent       = SE,
 
1253
                                 signalsDescriptor = SD}, State) ->
 
1254
    SE2 = tr_opt_SecondEventsDescriptor(SE, State),
 
1255
    SD2 = tr_opt_SignalsDescriptor(SD, State),
 
1256
    #'RegulatedEmbeddedDescriptor'{secondEvent       = SE2,
 
1257
                                   signalsDescriptor = SD2}.
 
1258
 
 
1259
tr_opt_NotifyBehaviour(asn1_NOVALUE, _State) ->
 
1260
    asn1_NOVALUE;
 
1261
tr_opt_NotifyBehaviour(NB, State) ->
 
1262
    tr_NotifyBehaviour(NB, State).
 
1263
 
 
1264
tr_NotifyBehaviour({notifyImmediate, 'NULL'} = NB, _State) ->
 
1265
    NB;
 
1266
tr_NotifyBehaviour({notifyRegulated = Tag, Val}, State) ->
 
1267
    {Tag, tr_RegulatedEmbeddedDescriptor(Val, State)};
 
1268
tr_NotifyBehaviour({neverNotify, 'NULL'} = NB, _State) ->
 
1269
    NB.
 
1270
 
 
1271
tr_opt_RequestedActions(asn1_NOVALUE, _State) ->
 
1272
    asn1_NOVALUE;
 
1273
tr_opt_RequestedActions(#'RequestedActions'{keepActive            = KA,
 
1274
                                            eventDM               = DM,
 
1275
                                            secondEvent           = SE,
 
1276
                                            signalsDescriptor     = SD,
 
1277
                                            notifyBehaviour       = NB,
 
1278
                                            resetEventsDescriptor = RSD},
 
1279
                        State) ->
 
1280
    KA2  = tr_opt_keepActive(KA, State),
 
1281
    DM2  = tr_opt_EventDM(DM, State),
 
1282
    SE2  = tr_opt_SecondEventsDescriptor(SE, State),
 
1283
    SD2  = tr_opt_SignalsDescriptor(SD, State),
 
1284
    NB2  = tr_opt_NotifyBehaviour(NB, State),
 
1285
    RSD2 = tr_opt_null(RSD, State),
 
1286
    #'RequestedActions'{keepActive            = KA2, 
 
1287
                        eventDM               = DM2, 
 
1288
                        secondEvent           = SE2,
 
1289
                        signalsDescriptor     = SD2,
 
1290
                        notifyBehaviour       = NB2,
 
1291
                        resetEventsDescriptor = RSD2}.
 
1292
 
 
1293
tr_opt_keepActive(asn1_NOVALUE, _State) ->
 
1294
    asn1_NOVALUE;
 
1295
tr_opt_keepActive(Keep, State) ->
 
1296
    tr_bool(Keep, State).
 
1297
 
 
1298
tr_opt_EventDM(asn1_NOVALUE, _State) ->
 
1299
    asn1_NOVALUE;
 
1300
tr_opt_EventDM({Tag, Val}, State) ->
 
1301
    Val2 = 
 
1302
        case Tag of
 
1303
            digitMapName  -> tr_DigitMapName(Val, State);
 
1304
            digitMapValue -> tr_DigitMapValue(Val, State)
 
1305
        end,
 
1306
    {Tag, Val2}.
 
1307
 
 
1308
tr_opt_SecondEventsDescriptor(asn1_NOVALUE, _State) ->
 
1309
    asn1_NOVALUE;
 
1310
tr_opt_SecondEventsDescriptor(#'SecondEventsDescriptor'{requestID = Id,
 
1311
                                                        eventList = Events},
 
1312
                              State) ->
 
1313
    #'SecondEventsDescriptor'{requestID = tr_RequestID(Id, State), %% IG v6 6.8 withdrawn
 
1314
                              eventList = [tr_SecondRequestedEvent(E, State) || E <- Events]}.
 
1315
 
 
1316
tr_SecondRequestedEvent(#'SecondRequestedEvent'{pkgdName    = Name,
 
1317
                                                streamID    = Id,
 
1318
                                                evParList   = Parms,
 
1319
                                                eventAction = Actions},
 
1320
                        State) ->
 
1321
    Constraint = fun(Item) -> tr_PkgdName(Item, State) end,
 
1322
    #'SecondRequestedEvent'{pkgdName    = resolve(event, Name, State, Constraint),
 
1323
                            streamID    = tr_opt_StreamID(Id, State),
 
1324
                            eventAction = tr_opt_SecondRequestedActions(Actions, State),
 
1325
                            evParList   = [tr_EventParameter(P, Name, State) || P <- Parms]}.
 
1326
 
 
1327
 
 
1328
tr_opt_SecondRequestedActions(asn1_NOVALUE, _State) ->
 
1329
    asn1_NOVALUE;
 
1330
tr_opt_SecondRequestedActions(
 
1331
  #'SecondRequestedActions'{keepActive            = KA,
 
1332
                            eventDM               = DM,
 
1333
                            signalsDescriptor     = SD,
 
1334
                            notifyBehaviour       = NB,
 
1335
                            resetEventsDescriptor = RSD},
 
1336
  State) ->
 
1337
    KA2  = tr_opt_keepActive(KA, State),
 
1338
    DM2  = tr_opt_EventDM(DM, State),
 
1339
    SD2  = tr_opt_SignalsDescriptor(SD, State), 
 
1340
    NB2  = tr_opt_NotifyBehaviour(NB, State),
 
1341
    RSD2 = tr_opt_null(RSD, State),
 
1342
    #'SecondRequestedActions'{keepActive            = KA2, 
 
1343
                              eventDM               = DM2, 
 
1344
                              signalsDescriptor     = SD2, 
 
1345
                              notifyBehaviour       = NB2,
 
1346
                              resetEventsDescriptor = RSD2}.
 
1347
 
 
1348
tr_EventBufferDescriptor(EventSpecs, State) ->
 
1349
    [tr_EventSpec(ES, State) || ES <- EventSpecs].
 
1350
 
 
1351
tr_EventSpec(#'EventSpec'{eventName    = Name,
 
1352
                          streamID     = Id,
 
1353
                          eventParList = Parms},
 
1354
             State) ->
 
1355
    #'EventSpec'{eventName    = tr_EventName(Name, State),
 
1356
                 streamID     = tr_opt_StreamID(Id, State),
 
1357
                 eventParList = [tr_EventParameter(P, Name, State) || P <- Parms]}.
 
1358
 
 
1359
tr_opt_SignalsDescriptor(asn1_NOVALUE, _State) ->
 
1360
    asn1_NOVALUE;
 
1361
tr_opt_SignalsDescriptor(SigDesc, State) ->
 
1362
    tr_SignalsDescriptor(SigDesc, State).
 
1363
 
 
1364
tr_SignalsDescriptor(SigDesc, State)  when list(SigDesc) ->
 
1365
    [tr_SignalRequest(SigReq, State) || SigReq <- SigDesc].
 
1366
 
 
1367
tr_SignalRequest({Tag, Val}, State) ->
 
1368
    Val2 =
 
1369
        case Tag of
 
1370
            signal     -> tr_Signal(Val, State);
 
1371
            seqSigList -> tr_SeqSigList(Val, State)
 
1372
        end,
 
1373
    {Tag, Val2}.
 
1374
 
 
1375
 
 
1376
tr_SeqSigList(#'SeqSigList'{id         = Id,
 
1377
                            signalList = SigList},
 
1378
              State) when list(SigList) ->
 
1379
    #'SeqSigList'{id         = tr_UINT16(Id, State),
 
1380
                  signalList = [tr_Signal(Sig, State) || Sig <- SigList]}.
 
1381
 
 
1382
tr_Signal(#'Signal'{signalName       = Name,
 
1383
                    streamID         = SID,
 
1384
                    sigType          = Type,
 
1385
                    duration         = Dur,
 
1386
                    notifyCompletion = Compl,
 
1387
                    keepActive       = Keep,
 
1388
                    sigParList       = Parms,
 
1389
                    direction        = Dir,
 
1390
                    requestID        = RID,
 
1391
                    intersigDelay    = ID},
 
1392
          State) ->
 
1393
    Name2  = tr_SignalName(Name, State),
 
1394
    SID2   = tr_opt_StreamID(SID, State),
 
1395
    Type2  = tr_opt_SignalType(Type, State),
 
1396
    Dur2   = tr_opt_UINT16(Dur, State), 
 
1397
    Compl2 = tr_opt_NotifyCompletion(Compl, State),
 
1398
    Keep2  = tr_opt_keepActive(Keep, State),
 
1399
    Parms2 = [tr_SigParameter(P, Name, State) || P <- Parms],
 
1400
    Dir2   = tr_opt_SignalDirection(Dir, State),
 
1401
    RID2   = tr_opt_RequestID(RID, State),
 
1402
    ID2    = tr_opt_UINT16(ID, State), 
 
1403
    #'Signal'{signalName       = Name2,
 
1404
              streamID         = SID2, 
 
1405
              sigType          = Type2, 
 
1406
              duration         = Dur2, 
 
1407
              notifyCompletion = Compl2, 
 
1408
              keepActive       = Keep2, 
 
1409
              sigParList       = Parms2,
 
1410
              direction        = Dir2,
 
1411
              requestID        = RID2,
 
1412
              intersigDelay    = ID2}.
 
1413
 
 
1414
tr_opt_NotifyCompletion(asn1_NOVALUE, _State) ->
 
1415
    asn1_NOVALUE;
 
1416
tr_opt_NotifyCompletion(Items, State) when list(Items) ->
 
1417
    [tr_notifyCompletionItem(I, State) || I <- Items].
 
1418
 
 
1419
tr_notifyCompletionItem(Item, _State) ->
 
1420
    case Item of
 
1421
        onTimeOut                   -> onTimeOut;
 
1422
        onInterruptByEvent          -> onInterruptByEvent;
 
1423
        onInterruptByNewSignalDescr -> onInterruptByNewSignalDescr;
 
1424
        otherReason                 -> otherReason;
 
1425
        onIteration                 -> onIteration
 
1426
    end.
 
1427
 
 
1428
tr_opt_SignalType(asn1_NOVALUE = Type, _State) ->
 
1429
    Type;
 
1430
tr_opt_SignalType(Type, _State) ->
 
1431
    case Type of
 
1432
        brief   -> brief;
 
1433
        onOff   -> onOff;
 
1434
        timeOut -> timeOut
 
1435
    end.
 
1436
 
 
1437
tr_opt_SignalDirection(asn1_NOVALUE = SD, _State) ->
 
1438
    SD;
 
1439
tr_opt_SignalDirection(SD, _State) ->
 
1440
    case SD of
 
1441
        internal -> internal;
 
1442
        external -> external;
 
1443
        both     -> both
 
1444
    end.
 
1445
             
 
1446
tr_SignalName(Name, State) ->
 
1447
    Constraint = fun(Item) -> tr_PkgdName(Item, State) end,
 
1448
    resolve(signal, Name, State, Constraint).
 
1449
 
 
1450
tr_SigParameter(#'SigParameter'{sigParameterName = ParName,
 
1451
                                value            = Value,
 
1452
                                extraInfo        = Extra},
 
1453
                SigName,
 
1454
                State) ->
 
1455
    Constraint = fun(Item) -> tr_Name(Item, State) end,
 
1456
    N = resolve({signal_parameter, SigName}, ParName, State, Constraint),
 
1457
    #'SigParameter'{sigParameterName = N,
 
1458
                    value            = tr_Value(Value, State),
 
1459
                    extraInfo        = tr_opt_extraInfo(Extra, State)}.
 
1460
 
 
1461
tr_opt_RequestID(asn1_NOVALUE, _State) ->
 
1462
    asn1_NOVALUE;
 
1463
tr_opt_RequestID(Id, State) ->
 
1464
    tr_RequestID(Id, State).
 
1465
 
 
1466
tr_RequestID(Id, _State) when Id == ?megaco_all_request_id ->
 
1467
    ?megaco_all_request_id;
 
1468
tr_RequestID(Id, State) ->
 
1469
    tr_UINT32(Id, State).
 
1470
 
 
1471
tr_ModemDescriptor(_MD, _State) ->
 
1472
    deprecated.
 
1473
 
 
1474
tr_DigitMapDescriptor(#'DigitMapDescriptor'{digitMapName  = Name,
 
1475
                                            digitMapValue = Value},
 
1476
                      State) ->
 
1477
    #'DigitMapDescriptor'{digitMapName  = tr_opt_DigitMapName(Name, State),
 
1478
                          digitMapValue = tr_opt_DigitMapValue(Value, State)}.
 
1479
 
 
1480
tr_opt_DigitMapName(asn1_NOVALUE, _State) ->
 
1481
    asn1_NOVALUE;
 
1482
tr_opt_DigitMapName(Name, State) ->
 
1483
    tr_DigitMapName(Name, State).
 
1484
 
 
1485
tr_DigitMapName(Name, State) ->
 
1486
    Constraint = fun(Item) -> tr_Name(Item, State) end,
 
1487
    resolve(dialplan, Name, State, Constraint).
 
1488
 
 
1489
tr_opt_DigitMapValue(asn1_NOVALUE, _State) ->
 
1490
    asn1_NOVALUE;
 
1491
tr_opt_DigitMapValue(Value, State) ->
 
1492
    tr_DigitMapValue(Value, State).
 
1493
 
 
1494
tr_DigitMapValue(#'DigitMapValue'{digitMapBody = Body,
 
1495
                                  startTimer   = Start,
 
1496
                                  shortTimer   = Short,
 
1497
                                  longTimer    = Long},
 
1498
                 State) ->
 
1499
    #'DigitMapValue'{startTimer   = tr_opt_timer(Start, State),
 
1500
                     shortTimer   = tr_opt_timer(Short, State),
 
1501
                     longTimer    = tr_opt_timer(Long, State),
 
1502
                     digitMapBody = tr_STRING(Body, State)}. %% BUGBUG: digitMapBody not handled at all
 
1503
 
 
1504
tr_opt_timer(asn1_NOVALUE, _State) ->
 
1505
    asn1_NOVALUE;
 
1506
tr_opt_timer(Timer, State) ->
 
1507
    tr_DIGIT(Timer, State, 0, 99).
 
1508
 
 
1509
tr_ServiceChangeParm(
 
1510
  #'ServiceChangeParm'{serviceChangeMethod  = Method, 
 
1511
                       serviceChangeAddress = Addr, 
 
1512
                       serviceChangeVersion = Version, 
 
1513
                       serviceChangeProfile = Profile, 
 
1514
                       serviceChangeReason  = Reason, 
 
1515
                       serviceChangeDelay   = Delay, 
 
1516
                       serviceChangeMgcId   = MgcId, 
 
1517
                       timeStamp            = Time,
 
1518
                       serviceChangeInfo    = Info,
 
1519
                       serviceChangeIncompleteFlag = Incomplete},
 
1520
  State) ->
 
1521
    Method2     = tr_ServiceChangeMethod(Method, State),
 
1522
    Addr2       = tr_opt_ServiceChangeAddress(Addr, State),
 
1523
    Version2    = tr_opt_serviceChangeVersion(Version, State),
 
1524
    Profile2    = tr_opt_ServiceChangeProfile(Profile, State),
 
1525
    Reason2     = tr_serviceChangeReason(Reason, State),
 
1526
    Delay2      = tr_opt_serviceChangeDelay(Delay, State),
 
1527
    MgcId2      = tr_opt_serviceChangeMgcId(MgcId, State),
 
1528
    Time2       = tr_opt_TimeNotation(Time, State),
 
1529
    Info2       = tr_opt_AuditDescriptor(Info, State),
 
1530
    Incomplete2 = tr_opt_null(Incomplete, State),
 
1531
    #'ServiceChangeParm'{serviceChangeMethod         = Method2,
 
1532
                         serviceChangeAddress        = Addr2,
 
1533
                         serviceChangeVersion        = Version2,
 
1534
                         serviceChangeProfile        = Profile2,
 
1535
                         serviceChangeReason         = Reason2, 
 
1536
                         serviceChangeDelay          = Delay2, 
 
1537
                         serviceChangeMgcId          = MgcId2, 
 
1538
                         timeStamp                   = Time2, 
 
1539
                         serviceChangeInfo           = Info2, 
 
1540
                         serviceChangeIncompleteFlag = Incomplete2}.
 
1541
 
 
1542
tr_ServiceChangeMethod(Method, _State) ->
 
1543
    case Method of
 
1544
        failover      -> failover;
 
1545
        forced        -> forced;
 
1546
        graceful      -> graceful;
 
1547
        restart       -> restart;
 
1548
        disconnected  -> disconnected;
 
1549
        handOff       -> handOff
 
1550
    end. %% BUGBUG: extension
 
1551
 
 
1552
tr_opt_ServiceChangeAddress(asn1_NOVALUE, _State) ->
 
1553
    asn1_NOVALUE;
 
1554
tr_opt_ServiceChangeAddress({Tag, Val}, State) ->
 
1555
    Val2 = 
 
1556
        case Tag of
 
1557
            portNumber -> tr_portNumber(Val, State);
 
1558
            ip4Address -> tr_IP4Address(Val, State);
 
1559
            ip6Address -> tr_IP6Address(Val, State);
 
1560
            domainName -> tr_DomainName(Val, State);
 
1561
            deviceName -> tr_PathName(Val, State);
 
1562
            mtpAddress -> tr_mtpAddress(Val, State)
 
1563
        end,
 
1564
    {Tag, Val2}.
 
1565
 
 
1566
tr_opt_serviceChangeVersion(asn1_NOVALUE, _State) ->
 
1567
    asn1_NOVALUE;
 
1568
tr_opt_serviceChangeVersion(Version, State) ->
 
1569
    tr_version(Version, State).
 
1570
 
 
1571
tr_opt_ServiceChangeProfile(asn1_NOVALUE, _State) ->
 
1572
    asn1_NOVALUE;
 
1573
%% Decode
 
1574
tr_opt_ServiceChangeProfile({'ServiceChangeProfile', ProfileName}, State) ->
 
1575
    case string:tokens(ProfileName, "/") of
 
1576
        [Name0, Version0] ->
 
1577
            Name    = tr_STRING(Name0, State, 1, 64),
 
1578
            Version = tr_version(list_to_integer(Version0), State),
 
1579
            #'ServiceChangeProfile'{profileName = Name, 
 
1580
                                    version     = Version}
 
1581
    end;
 
1582
%% Encode
 
1583
tr_opt_ServiceChangeProfile(#'ServiceChangeProfile'{profileName = Name0, 
 
1584
                                                    version     = Version0},
 
1585
                            State) ->
 
1586
    Name        = tr_STRING(Name0, State, 1, 64),
 
1587
    Version     = tr_version(Version0, State),
 
1588
    ProfileName = lists:flatten(io_lib:format("~s/~w", [Name, Version])),
 
1589
    {'ServiceChangeProfile', ProfileName}.
 
1590
    
 
1591
tr_serviceChangeReason([_] = Reason, State) ->
 
1592
    tr_Value(Reason, State).
 
1593
 
 
1594
tr_opt_serviceChangeDelay(asn1_NOVALUE, _State) ->
 
1595
    asn1_NOVALUE;
 
1596
tr_opt_serviceChangeDelay(Delay, State) ->
 
1597
    tr_UINT32(Delay, State).
 
1598
 
 
1599
tr_opt_serviceChangeMgcId(asn1_NOVALUE, _State) ->
 
1600
    asn1_NOVALUE;
 
1601
tr_opt_serviceChangeMgcId(MgcId, State) ->
 
1602
    tr_MId(MgcId, State).
 
1603
 
 
1604
tr_opt_portNumber(asn1_NOVALUE, _State) ->
 
1605
    asn1_NOVALUE;
 
1606
tr_opt_portNumber(Port, State) ->
 
1607
    tr_portNumber(Port, State).
 
1608
 
 
1609
tr_portNumber(Port, State) when integer(Port), Port >= 0 ->
 
1610
    tr_UINT16(Port, State).
 
1611
 
 
1612
tr_ServiceChangeResParm(#'ServiceChangeResParm'{serviceChangeMgcId   = MgcId, 
 
1613
                                                serviceChangeAddress = Addr, 
 
1614
                                                serviceChangeVersion = Version, 
 
1615
                                                serviceChangeProfile = Profile,
 
1616
                                                timeStamp            = Time}, 
 
1617
                        State) ->
 
1618
    #'ServiceChangeResParm'{serviceChangeMgcId   = tr_opt_serviceChangeMgcId(MgcId, State),
 
1619
                            serviceChangeAddress = tr_opt_ServiceChangeAddress(Addr, State),
 
1620
                            serviceChangeVersion = tr_opt_serviceChangeVersion(Version, State),
 
1621
                            serviceChangeProfile = tr_opt_ServiceChangeProfile(Profile, State),
 
1622
                            timeStamp            = tr_opt_TimeNotation(Time, State)}.
 
1623
 
 
1624
tr_PackagesDescriptor(Items, State) when list(Items) ->
 
1625
    [tr_PackagesItem(I, State) || I <- Items].
 
1626
 
 
1627
tr_PackagesItem(#'PackagesItem'{packageName    = Name,
 
1628
                                packageVersion = Version},
 
1629
                State) ->
 
1630
    Constraint = fun(Item) -> tr_Name(Item, State) end,
 
1631
    #'PackagesItem'{packageName    = resolve(package, Name, State, Constraint),
 
1632
                    packageVersion = tr_UINT16(Version, State)}.
 
1633
 
 
1634
tr_opt_StatisticsDescriptor(asn1_NOVALUE, _State) ->
 
1635
    asn1_NOVALUE;
 
1636
tr_opt_StatisticsDescriptor(Parms, State) ->
 
1637
    tr_StatisticsDescriptor(Parms, State).
 
1638
 
 
1639
tr_StatisticsDescriptor(Parms, State) when list(Parms) ->
 
1640
    [tr_StatisticsParameter(P, State) || P <- Parms].
 
1641
 
 
1642
tr_StatisticsParameter(#'StatisticsParameter'{statName  = Name,
 
1643
                                              statValue = Value},
 
1644
                       State) ->
 
1645
    Constraint = fun(Item) -> tr_PkgdName(Item, State) end,
 
1646
    #'StatisticsParameter'{statName  = resolve(statistics, Name, State, Constraint),
 
1647
                           statValue = tr_opt_Value(Value, State)}.
 
1648
 
 
1649
tr_opt_TimeNotation(asn1_NOVALUE, _State) ->
 
1650
    asn1_NOVALUE;
 
1651
tr_opt_TimeNotation(#'TimeNotation'{date = Date,
 
1652
                                    time = Time},
 
1653
                    State) ->
 
1654
    #'TimeNotation'{date = tr_STRING(Date, State, 8, 8), % "yyyymmdd"
 
1655
                    time = tr_STRING(Time, State, 8, 8)}.% "hhmmssss"
 
1656
 
 
1657
%% BUGBUG: Does not verify that string must contain at least one char
 
1658
%% BUGBUG: This violation of the is required in order to comply with
 
1659
%% BUGBUG: the dd/ce ds parameter that may possibly be empty.
 
1660
 
 
1661
tr_opt_Value(asn1_NOVALUE, _State) ->
 
1662
    asn1_NOVALUE;
 
1663
tr_opt_Value(Value, State) ->
 
1664
    tr_Value(Value, State).
 
1665
 
 
1666
tr_Value(Strings, _State) when list(Strings) ->
 
1667
    [[Char || Char <- String] || String <- Strings].
 
1668
 
 
1669
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1670
 
 
1671
%% Encode an octet string, escape } by \ if necessary 
 
1672
tr_OCTET_STRING(String, _State, Min, Max) when list(String) ->
 
1673
    verify_count(length(String), Min, Max),
 
1674
    String.
 
1675
 
 
1676
tr_QUOTED_STRING(String, _State) when list(String) ->
 
1677
    verify_count(length(String), 1, infinity),
 
1678
    String.
 
1679
 
 
1680
%% The internal format of hex digits is a list of octets
 
1681
%% Min and Max means #hexDigits
 
1682
%% Leading zeros are prepended in order to fulfill Min
 
1683
tr_HEXDIG(Octets, _State, Min, Max) when list(Octets) ->
 
1684
    verify_count(length(Octets), Min, Max),
 
1685
    Octets.
 
1686
 
 
1687
tr_DIGIT(Val, State, Min, Max) ->
 
1688
    tr_integer(Val, State, Min, Max).
 
1689
 
 
1690
tr_STRING(String, _State) when list(String) ->
 
1691
    String.
 
1692
 
 
1693
tr_STRING(String, _State, Min, Max) when list(String) ->
 
1694
    verify_count(length(String), Min, Max),
 
1695
    String.
 
1696
 
 
1697
tr_opt_UINT16(Val, State) ->
 
1698
    tr_opt_integer(Val, State, 0, 65535).
 
1699
 
 
1700
tr_UINT16(Val, State) ->
 
1701
    tr_integer(Val, State, 0, 65535).
 
1702
 
 
1703
tr_UINT32(Val, State) ->
 
1704
    tr_integer(Val, State, 0, 4294967295).
 
1705
 
 
1706
tr_opt_integer(asn1_NOVALUE, _State, _Min, _Max) ->
 
1707
    asn1_NOVALUE;
 
1708
tr_opt_integer(Int, State, Min, Max) ->
 
1709
    tr_integer(Int, State, Min, Max).
 
1710
 
 
1711
tr_integer(Int, _State, Min, Max) ->
 
1712
    verify_count(Int, Min, Max),
 
1713
    Int.
 
1714
 
 
1715
%% Verify that Count is within the range of Min and Max
 
1716
verify_count(Count, Min, Max) ->
 
1717
    if
 
1718
        integer(Count) ->
 
1719
            if
 
1720
                integer(Min), Count >= Min ->
 
1721
                    if
 
1722
                        integer(Max), Count =< Max ->
 
1723
                            Count;
 
1724
                        Max == infinity ->
 
1725
                            Count;
 
1726
                        true ->
 
1727
                            error({count_too_large, Count, Max})
 
1728
                    end;
 
1729
                true ->
 
1730
                    error({count_too_small, Count, Min})
 
1731
            end;
 
1732
        true ->
 
1733
            error({count_not_an_integer, Count})
 
1734
    end.
 
1735
 
 
1736
 
 
1737
%% -------------------------------------------------------------------
 
1738
 
 
1739
error(Reason) ->
 
1740
    erlang:fault(Reason).
 
1741
 
 
1742