~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/asn1/test/asn1_SUITE_data/OLD-MEDIA-GATEWAY-CONTROL.asn

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
-- This ASN.1 spec has been extracted from the Megaco/H.248 spec
 
2
-- http://www.ietf.org/internet-drafts/draft-ietf-megaco-merged-01.txt
 
3
--
 
4
-- o Removed stuff named nonStandard
 
5
-- o Major enhancements of the indentation has been performed.
 
6
--
 
7
-- Hakan Mattsson <hakan@cslab.ericsson.se>
 
8
--
 
9
-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- --
 
10
-- ANNEX A: BINARY ENCODING OF THE PROTOCOL (NORMATIVE) 
 
11
-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- --
 
12
--     
 
13
-- This Annex specifies the syntax of messages using the notation 
 
14
-- defined in ASN.1 [ITU-T Recommendation X.680 (1997): Information 
 
15
-- Technology - Abstract Syntax Notation One (ASN.1) - Specification of 
 
16
-- basic notation.]. Messages shall be encoded for transmission by 
 
17
-- applying the basic encoding rules specified in [ITU-T Recommendation 
 
18
-- X.690(1994) Information Technology - ASN.1  Encoding Rules: 
 
19
-- Specification of Basic Encoding Rules (BER)].  
 
20
--     
 
21
-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- --
 
22
-- A.1 Coding of wildcards 
 
23
-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- --
 
24
--     
 
25
-- The use of wildcards ALL and CHOOSE is allowed in the protocol.  
 
26
-- This allows a MGC to partially specify Termination IDs and let the 
 
27
-- MG choose from the values that conform to the partial specification.  
 
28
-- Termination IDs may encode a hierarchy of names.  This hierarchy is 
 
29
-- provisioned. For instance, a TerminationID may consist of a trunk 
 
30
-- group, a trunk within the group and a circuit.  Wildcarding must be 
 
31
-- possible at all levels.  The following paragraphs explain how this 
 
32
-- is achieved. 
 
33
--  
 
34
-- The ASN.1 description uses octet strings of up to 8 octets in length 
 
35
-- for Termination IDs.  This means that Termination IDs consist of at 
 
36
-- most 64 bits.  A fully specified Termination ID may be preceded by a 
 
37
-- sequence of wildcarding fields.  A wildcarding field is one octet in 
 
38
-- length.  Bit 7 (the most significant bit) of this octet specifies 
 
39
-- what type of wildcarding is invoked:  if the bit value equals 1, 
 
40
-- then the ALL wildcard is used; if the bit value if 0, then the 
 
41
-- CHOOSE wildcard is used.  Bit 6 of the wildcarding field specifies 
 
42
-- whether the wildcarding pertains to one level in the hierarchical 
 
43
-- naming scheme (bit value 0) or to the level of the hierarchy 
 
44
-- specified in the wildcarding field plus all lower levels (bit value 
 
45
-- 1).  Bits 0 through 5 of the wildcarding field specify the bit 
 
46
-- position in the Termination ID at which the starts. 
 
47
--  
 
48
-- We illustrate this scheme with some examples.  In these examples, 
 
49
-- the most significant bit in a string of bits appears on the left 
 
50
-- hand side. 
 
51
--  
 
52
-- Assume that Termination IDs are three octets long and that each 
 
53
-- octet represents a level in a hierarchical naming scheme.  A valid 
 
54
-- Termination ID is 
 
55
--      00000001 00011110 01010101. 
 
56
--  
 
57
-- Addressing ALL names with prefix 00000001 00011110 is done as 
 
58
-- follows: 
 
59
--      wildcarding field: 10000111 
 
60
--      Termination ID: 00000001 00011110 xxxxxxxx. 
 
61
--  
 
62
-- The values of the bits labeled "x" is irrelevant and shall be 
 
63
-- ignored by the receiver. 
 
64
-- 
 
65
-- Indicating to the receiver that is must choose a name with 00011110 
 
66
-- as the second octet is done as follows: 
 
67
--      wildcarding fields: 00010111 followed by 00000111 
 
68
--      Termination ID: xxxxxxxx 00011110 xxxxxxxx. 
 
69
--  
 
70
-- The first wildcard field indicates a CHOOSE wildcard for the level 
 
71
-- in the naming hierarchy starting at bit 23, the highest level in our 
 
72
-- assumed naming scheme.  The second wildcard field indicates a CHOOSE 
 
73
-- wildcard for the level in the naming hierarchy starting at bit 7, 
 
74
-- the lowest level in our assumed naming scheme. 
 
75
--  
 
76
-- Finally, a CHOOSE-wildcarded name with the highest level of the name 
 
77
-- equal to 00000001 is specified as follows: 
 
78
--      wildcard field: 01001111 
 
79
--      Termination ID: 0000001 xxxxxxxx xxxxxxxx . 
 
80
--  
 
81
-- Bit value 1 at bit position 6 of the first octet of the wildcard 
 
82
-- field indicates that the wildcarding pertains to the specified level 
 
83
-- in the naming hierarchy and all lower levels. 
 
84
--  
 
85
-- Context IDs may also be wildcarded.  In the case of Context IDs, 
 
86
-- however, specifying partial names is not allowed.  Context ID 0x0  
 
87
-- SHALL be used to indicate the NULL Context, Context ID 0xFFFFFFFE 
 
88
-- SHALL be used to indicate a CHOOSE wildcard, and Context ID 
 
89
-- 0xFFFFFFFF SHALL be used to indicate an ALL wildcard. 
 
90
--  
 
91
-- TerminationID 0xFFFFFFFFFFFFFFFF SHALL be used to indicate the ROOT 
 
92
-- Termination. 
 
93
--     
 
94
-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- --
 
95
-- Digit maps and path names 
 
96
-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- --
 
97
--  
 
98
-- From a syntactic viewpoint, digit maps are strings with syntactic 
 
99
-- restrictions imposed upon them.  The syntax of valid digit maps is 
 
100
-- specified in ABNF [RFC 2234].  The syntax for digit maps presented 
 
101
-- in this section is for illustrative purposes only. The definition of 
 
102
-- digitMap in Annex B takes precedence in the case of differences 
 
103
-- between the two. 
 
104
--  
 
105
-- digitMap = (digitString / LWSP "(" LWSP digitStringList LWSP ")" 
 
106
-- LWSP) 
 
107
-- digitStringList = digitString *( LWSP "/" LWSP digitString ) 
 
108
-- digitString = 1*(digitStringElement) 
 
109
-- digitStringElement = digitPosition [DOT] 
 
110
-- digitPosition = digitMapLetter / digitMapRange 
 
111
-- digitMapRange = ("x" / LWSP "[" LWSP digitLetter LWSP "]" LWSP) 
 
112
-- digitLetter = *((DIGIT "-" DIGIT) /digitMapLetter) 
 
113
-- digitMapLetter = DIGIT               ;digits 0-9 
 
114
--         / %x41-4B / %x61-6B             ;a-k and A-K 
 
115
--         / "L"   / "S"                   ;Inter-event timers 
 
116
--                                         ;(long, short) 
 
117
--         / "Z"                           ;Long duration event 
 
118
-- DOT = %x2E ; "." 
 
119
-- LWSP = *(WSP / COMMENT / EOL) 
 
120
-- WSP = SP / HTAB 
 
121
-- COMMENT = ";" *(SafeChar / RestChar / WSP) EOL 
 
122
-- EOL = (CR [LF]) / LF 
 
123
-- SP = %x20 
 
124
-- HTAB = %x09 
 
125
-- CR = %x0D 
 
126
-- LF = %x0A 
 
127
-- SafeChar = DIGIT / ALPHA / "+" / "-" / "&" / "!" / "_" / "/" / 
 
128
--  "'" / "?" / "@" / "^" / "`" / "~" / "*" / "$" / "\" / 
 
129
-- "(" / ")" / "%" / "." 
 
130
-- RestChar = ";" / "[" / "]" / "{" / "}" / ":" / "," / "#" / 
 
131
--                 "<" / ">" / "=" / %x22 
 
132
-- DIGIT = %x30-39                      ; digits 0 through 9 
 
133
-- ALPHA = %x41-5A / %x61-7A    ; A-Z, a-z 
 
134
-- A path name is also a string with syntactic restrictions imposed 
 
135
-- upon it.  The ABNF production defining it is copied from Annex B. 
 
136
--  
 
137
-- PathName = NAME *(["/"] ["*"] ["@"] (ALPHA / DIGIT)) ["*"] 
 
138
-- NAME = ALPHA *63(ALPHA / DIGIT / "_" )
 
139
--
 
140
-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- --
 
141
-- A.2 ASN.1 syntax specification 
 
142
-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- --
 
143
--     
 
144
-- This section contains the ASN.1 specification of the H.248 protocol 
 
145
-- syntax. 
 
146
--  
 
147
-- NOTE - In case a transport mechanism is used that employs 
 
148
-- application level framing, the definition of Transaction below 
 
149
-- changes.  Refer to the annex defining the transport mechanism for 
 
150
-- the definition that applies in that case. 
 
151
--  
 
152
-- NOTE - The ASN.1 specification below contains a clause defining 
 
153
-- TerminationIDList as a sequence of TerminationIDs.  The length of 
 
154
-- this sequence SHALL be one, except possibly when used in 
 
155
-- contextAuditResult. 
 
156
-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- --
 
157
 
 
158
OLD-MEDIA-GATEWAY-CONTROL DEFINITIONS AUTOMATIC TAGS::= 
 
159
BEGIN 
 
160
 
 
161
MegacoMessage ::= SEQUENCE 
 
162
 
163
     authHeader                 AuthenticationHeader OPTIONAL, 
 
164
     mess                       Message 
 
165
 
166
 
 
167
AuthenticationHeader ::= SEQUENCE 
 
168
 
169
     secParmIndex               SecurityParmIndex, 
 
170
     seqNum                     SequenceNum, 
 
171
     ad                         AuthData 
 
172
 
173
 
 
174
SecurityParmIndex ::= OCTET STRING(SIZE(4)) 
 
175
 
 
176
SequenceNum       ::= OCTET STRING(SIZE(4)) 
 
177
 
 
178
AuthData          ::= OCTET STRING (SIZE (12..32)) 
 
179
 
 
180
Message ::= SEQUENCE 
 
181
{
 
182
        version         INTEGER(0..99), 
 
183
        -- The version of the protocol defined here is equal to 1. 
 
184
             mId             MId,    -- Name/address of message originator 
 
185
             messageBody             CHOICE 
 
186
             { 
 
187
                     messageError    ErrorDescriptor, 
 
188
                     transactions    SEQUENCE OF Transaction 
 
189
             }, 
 
190
        ... 
 
191
 
192
 
 
193
MId ::= CHOICE 
 
194
 
195
        ip4Address              IP4Address, 
 
196
        ip6Address              IP6Address, 
 
197
        domainName              DomainName, 
 
198
        deviceName              PathName, 
 
199
        mtpAddress              OCTET STRING(SIZE(2)), 
 
200
        -- Addressing structure of mtpAddress: 
 
201
        --        15                0 
 
202
        --        |  PC        | NI | 
 
203
        --           14 bits    2 bits 
 
204
      ... 
 
205
 
206
 
 
207
DomainName ::= SEQUENCE 
 
208
 
209
        name                    IA5String, 
 
210
        -- The name starts with an alphanumeric digit followed by a 
 
211
        -- sequence of alphanumeric digits, hyphens and dots.  No two 
 
212
        -- dots shall occur consecutively. 
 
213
        portNumber              INTEGER(0..65535) OPTIONAL 
 
214
 
215
 
 
216
IP4Address ::= SEQUENCE 
 
217
 
218
        address                 OCTET STRING (SIZE(4)), 
 
219
        portNumber              INTEGER(0..65535) OPTIONAL 
 
220
 
221
 
 
222
IP6Address ::= SEQUENCE 
 
223
 
224
        address                 OCTET STRING (SIZE(16)), 
 
225
        portNumber              INTEGER(0..65535) OPTIONAL 
 
226
 
227
 
 
228
PathName ::= IA5String(SIZE (1..64)) 
 
229
-- See section A.3 
 
230
 
 
231
Transaction ::= CHOICE 
 
232
 
233
        transactionRequest      TransactionRequest, 
 
234
        transactionPending      TransactionPending, 
 
235
        transactionReply        TransactionReply, 
 
236
        transactionResponseAck  TransactionResponseAck, 
 
237
             -- use of response acks is dependent on underlying transport 
 
238
        ... 
 
239
 
240
 
 
241
TransactionId ::= INTEGER(0..4294967295)  -- 32 bit unsigned integer 
 
242
 
 
243
TransactionRequest ::= SEQUENCE 
 
244
 
245
        transactionId           TransactionId, 
 
246
        actions                 SEQUENCE OF ActionRequest, 
 
247
        ... 
 
248
 
249
 
 
250
TransactionPending ::= SEQUENCE 
 
251
 
252
        transactionId           TransactionId, 
 
253
        ... 
 
254
 
255
 
 
256
TransactionReply ::= SEQUENCE 
 
257
 
258
        transactionId           TransactionId, 
 
259
        immAckRequired          NULL OPTIONAL,
 
260
        transactionResult       CHOICE 
 
261
        {  
 
262
             transactionError   ErrorDescriptor, 
 
263
             actionReplies      SEQUENCE OF ActionReply 
 
264
        }, 
 
265
        ... 
 
266
 
267
 
 
268
TransactionResponseAck ::= SEQUENCE 
 
269
 
270
        firstAck                TransactionId, 
 
271
        lastAck                 TransactionId OPTIONAL 
 
272
 
273
 
 
274
ErrorDescriptor ::= SEQUENCE 
 
275
 
276
        errorCode               ErrorCode, 
 
277
        errorText               ErrorText OPTIONAL 
 
278
 
279
 
 
280
ErrorCode ::= INTEGER(0..65535) 
 
281
-- See section 13 for IANA considerations w.r.t. error codes 
 
282
 
 
283
ErrorText ::= IA5String 
 
284
 
 
285
ContextID ::= INTEGER(0..4294967295) 
 
286
 
 
287
-- Context NULL Value:    0 
 
288
-- Context CHOOSE Value: 4294967294 (0xFFFFFFFE)  
 
289
-- Context ALL Value:    4294967295 (0xFFFFFFFF) 
 
290
 
 
291
 
 
292
ActionRequest ::= SEQUENCE 
 
293
 
294
        contextId               ContextID, 
 
295
        contextRequest          ContextRequest OPTIONAL, 
 
296
        contextAttrAuditReq     ContextAttrAuditRequest OPTIONAL, 
 
297
        commandRequests         SEQUENCE OF CommandRequest 
 
298
 
299
 
 
300
ActionReply ::= SEQUENCE 
 
301
 
302
        contextId               ContextID, 
 
303
        errorDescriptor         ErrorDescriptor OPTIONAL, 
 
304
        contextReply            ContextRequest OPTIONAL, 
 
305
        commandReply            SEQUENCE OF CommandReply 
 
306
 
307
 
 
308
ContextRequest ::= SEQUENCE 
 
309
 
310
        priority                INTEGER(0..15) OPTIONAL, 
 
311
        emergency               BOOLEAN OPTIONAL, 
 
312
        topologyReq             SEQUENCE OF TopologyRequest OPTIONAL, 
 
313
        ... 
 
314
 
315
 
 
316
ContextAttrAuditRequest ::= SEQUENCE 
 
317
 
318
        topology                NULL OPTIONAL, 
 
319
        emergency               NULL OPTIONAL, 
 
320
        priority                NULL OPTIONAL, 
 
321
        ... 
 
322
 
323
 
 
324
CommandRequest ::= SEQUENCE 
 
325
 
326
        command                 Command, 
 
327
        optional                NULL OPTIONAL, 
 
328
        wildcardReturn          NULL OPTIONAL, 
 
329
        ... 
 
330
 
331
 
 
332
Command ::= CHOICE 
 
333
 
334
        addReq                  AmmRequest, 
 
335
        moveReq                 AmmRequest, 
 
336
        modReq                  AmmRequest, 
 
337
        -- Add, Move, Modify requests have the same parameters 
 
338
        subtractReq             SubtractRequest, 
 
339
        auditCapRequest         AuditRequest, 
 
340
        auditValueRequest       AuditRequest, 
 
341
        notifyReq               NotifyRequest, 
 
342
        serviceChangeReq        ServiceChangeRequest, 
 
343
        ... 
 
344
 
345
 
 
346
CommandReply ::= CHOICE 
 
347
 
348
        addReply                AmmsReply, 
 
349
        moveReply               AmmsReply, 
 
350
        modReply                AmmsReply, 
 
351
        subtractReply           AmmsReply, 
 
352
        -- Add, Move, Modify, Subtract replies have the same parameters 
 
353
        auditCapReply           AuditReply, 
 
354
        auditValueReply         AuditReply, 
 
355
        notifyReply             NotifyReply, 
 
356
        serviceChangeReply      ServiceChangeReply, 
 
357
        ... 
 
358
 
359
 
 
360
TopologyRequest ::= SEQUENCE 
 
361
 
362
        terminationFrom         TerminationID, 
 
363
        terminationTo           TerminationID, 
 
364
        topologyDirection       ENUMERATED 
 
365
        { 
 
366
                bothway(0), 
 
367
                isolate(1), 
 
368
                oneway(2) 
 
369
        } 
 
370
 
371
 
 
372
AmmRequest ::= SEQUENCE 
 
373
 
374
        terminationID           TerminationIDList, 
 
375
        descriptors             SEQUENCE OF     AmmDescriptor, 
 
376
        -- At most one descriptor of each type (see AmmDescriptor) 
 
377
        -- allowed in the sequence. 
 
378
        ... 
 
379
 
380
 
 
381
AmmDescriptor ::= CHOICE 
 
382
 
383
        mediaDescriptor         MediaDescriptor, 
 
384
        modemDescriptor         ModemDescriptor, 
 
385
        muxDescriptor           MuxDescriptor, 
 
386
        eventsDescriptor        EventsDescriptor, 
 
387
        eventBufferDescriptor   EventBufferDescriptor, 
 
388
        signalsDescriptor       SignalsDescriptor, 
 
389
        digitMapDescriptor      DigitMapDescriptor, 
 
390
        auditDescriptor         AuditDescriptor, 
 
391
... 
 
392
 
393
 
 
394
AmmsReply ::= SEQUENCE 
 
395
 
396
        terminationID           TerminationIDList, 
 
397
        terminationAudit        TerminationAudit OPTIONAL, 
 
398
        ... 
 
399
 
400
 
 
401
SubtractRequest ::= SEQUENCE 
 
402
 
403
        terminationID           TerminationIDList, 
 
404
        auditDescriptor         AuditDescriptor OPTIONAL, 
 
405
        ... 
 
406
 
407
 
 
408
AuditRequest ::= SEQUENCE 
 
409
 
410
        terminationID           TerminationID, 
 
411
        auditDescriptor         AuditDescriptor, 
 
412
        ... 
 
413
 
414
 
 
415
AuditReply ::= SEQUENCE 
 
416
 
417
        terminationID           TerminationID, 
 
418
        auditResult             AuditResult, 
 
419
        ... 
 
420
 
421
 
 
422
AuditResult ::= CHOICE 
 
423
 
424
        contextAuditResult      TerminationIDList, 
 
425
        terminationAuditResult  TerminationAudit 
 
426
 
427
 
 
428
 
 
429
 
 
430
TerminationAudit ::= SEQUENCE OF AuditReturnParameter 
 
431
 
 
432
AuditReturnParameter ::= CHOICE 
 
433
 
434
        errorDescriptor          ErrorDescriptor, 
 
435
        mediaDescriptor          MediaDescriptor, 
 
436
        modemDescriptor          ModemDescriptor, 
 
437
        muxDescriptor            MuxDescriptor, 
 
438
        eventsDescriptor         EventsDescriptor, 
 
439
        eventBufferDescriptor    EventBufferDescriptor, 
 
440
        signalsDescriptor        SignalsDescriptor, 
 
441
        digitMapDescriptor       DigitMapDescriptor, 
 
442
        observedEventsDescriptor ObservedEventsDescriptor, 
 
443
        statisticsDescriptor     StatisticsDescriptor, 
 
444
        packagesDescriptor       PackagesDescriptor, 
 
445
        emptyDescriptors         AuditDescriptor, 
 
446
        ... 
 
447
 
448
 
 
449
AuditDescriptor ::= SEQUENCE 
 
450
 
451
        auditToken              BIT STRING 
 
452
        { 
 
453
                muxToken(0),
 
454
                modemToken(1),
 
455
                mediaToken(2), 
 
456
                eventsToken(3),
 
457
                signalsToken(4), 
 
458
                digitMapToken(5),
 
459
                statsToken(6), 
 
460
                observedEventsToken(7), 
 
461
                packagesToken(8),
 
462
                eventBufferToken(9) 
 
463
        } OPTIONAL, 
 
464
        ... 
 
465
 
466
 
 
467
NotifyRequest ::= SEQUENCE 
 
468
 
469
        terminationID            TerminationIDList, 
 
470
        observedEventsDescriptor ObservedEventsDescriptor, 
 
471
        errorDescriptor          ErrorDescriptor OPTIONAL, 
 
472
        ... 
 
473
 
474
 
 
475
NotifyReply ::= SEQUENCE 
 
476
 
477
        terminationID           TerminationIDList OPTIONAL, 
 
478
        errorDescriptor         ErrorDescriptor OPTIONAL, 
 
479
        ... 
 
480
 
481
 
 
482
ObservedEventsDescriptor ::= SEQUENCE 
 
483
 
484
        requestId               RequestID, 
 
485
        observedEventLst        SEQUENCE OF ObservedEvent 
 
486
 
487
 
 
488
ObservedEvent ::= SEQUENCE 
 
489
 
490
        eventName               EventName, 
 
491
        streamID                StreamID OPTIONAL, 
 
492
        eventParList            SEQUENCE OF EventParameter, 
 
493
        timeNotation            TimeNotation OPTIONAL, 
 
494
        ... 
 
495
 
496
 
 
497
EventName ::= PkgdName 
 
498
 
 
499
EventParameter ::= SEQUENCE 
 
500
 
501
        eventParameterName      Name, 
 
502
        value                   Value 
 
503
 
504
 
 
505
ServiceChangeRequest ::= SEQUENCE 
 
506
 
507
        terminationID           TerminationIDList, 
 
508
        serviceChangeParms      ServiceChangeParm, 
 
509
        ... 
 
510
 
511
 
 
512
ServiceChangeReply ::= SEQUENCE 
 
513
 
514
        terminationID           TerminationIDList, 
 
515
        serviceChangeResult     ServiceChangeResult, 
 
516
        ... 
 
517
 
518
 
 
519
-- For ServiceChangeResult, no parameters are mandatory.  Hence the 
 
520
-- distinction between ServiceChangeParm and ServiceChangeResParm. 
 
521
 
 
522
ServiceChangeResult ::= CHOICE 
 
523
 
524
        errorDescriptor         ErrorDescriptor, 
 
525
        serviceChangeResParms   ServiceChangeResParm 
 
526
 
527
 
 
528
WildcardField ::= OCTET STRING(SIZE(1)) 
 
529
 
 
530
TerminationID ::= SEQUENCE 
 
531
 
532
        wildcard                SEQUENCE OF WildcardField,  
 
533
        id                      OCTET STRING(SIZE(1..8)), 
 
534
        ... 
 
535
 
536
-- See Section A.1 for explanation of wildcarding mechanism. 
 
537
-- Termination ID 0xFFFFFFFFFFFFFFFF indicates the ROOT Termination. 
 
538
 
 
539
TerminationIDList ::= SEQUENCE OF TerminationID 
 
540
 
 
541
MediaDescriptor ::= SEQUENCE 
 
542
 
543
         
 
544
        termStateDescr          TerminationStateDescriptor OPTIONAL, 
 
545
        streams                 CHOICE 
 
546
        { 
 
547
                oneStream       StreamParms, 
 
548
                multiStream     SEQUENCE OF StreamDescriptor 
 
549
        }, 
 
550
        ... 
 
551
 
552
 
 
553
StreamDescriptor ::= SEQUENCE 
 
554
 
555
        streamID                StreamID, 
 
556
        streamParms             StreamParms 
 
557
 
558
 
 
559
StreamParms ::= SEQUENCE 
 
560
 
561
        localControlDescriptor  LocalControlDescriptor OPTIONAL, 
 
562
        localDescriptor         LocalRemoteDescriptor OPTIONAL,
 
563
        remoteDescriptor        LocalRemoteDescriptor OPTIONAL, 
 
564
        ... 
 
565
 
566
 
 
567
LocalControlDescriptor ::= SEQUENCE 
 
568
 
569
        streamMode              StreamMode OPTIONAL, 
 
570
        reserveValue            BOOLEAN, 
 
571
        reserveGroup            BOOLEAN, 
 
572
        propertyParms           SEQUENCE OF PropertyParm, 
 
573
        ... 
 
574
 
575
 
 
576
StreamMode ::= ENUMERATED  
 
577
 
578
        sendOnly(0), 
 
579
        recvOnly(1), 
 
580
        sendRecv(2), 
 
581
        inactive(3), 
 
582
        loopBack(4), 
 
583
                ... 
 
584
 
585
 
 
586
-- In PropertyParm, value is a SEQUENCE OF octet string.  When sent 
 
587
-- by an MGC the interpretation is as follows: 
 
588
-- empty sequence means CHOOSE 
 
589
-- one element sequence specifies value 
 
590
-- If the sublist field is not selected, a longer sequence means  
 
591
-- "choose one of the values" (i.e. value1 OR value2 OR ...) 
 
592
-- If the sublist field is selected, 
 
593
-- a sequence with more than one element encodes the value of a 
 
594
-- list-valued property (i.e. value1 AND value2 AND ...).
 
595
-- The relation field may only be selected if the value sequence 
 
596
-- has length 1.  It indicates that the MG has to choose a value 
 
597
-- for the property. E.g., x > 3 (using the greaterThan 
 
598
-- value for relation) instructs the MG to choose any value larger 
 
599
-- than 3 for property x. 
 
600
-- The range field may only be selected if the value sequence 
 
601
-- has length 2.  It indicates that the MG has to choose a value 
 
602
-- in the range between the first octet in the value sequence and 
 
603
-- the trailing octet in the value sequence, including the 
 
604
-- boundary values. 
 
605
-- When sent by the MG, only responses to an AuditCapability request 
 
606
-- may contain multiple values, a range, or a relation field. 
 
607
 
 
608
PropertyParm ::= SEQUENCE 
 
609
 
610
        name                    PkgdName, 
 
611
        value                   SEQUENCE OF OCTET STRING, 
 
612
        extraInfo               CHOICE 
 
613
        { 
 
614
                relation        Relation, 
 
615
                range           BOOLEAN, 
 
616
                sublist         BOOLEAN 
 
617
        } OPTIONAL, 
 
618
        ... 
 
619
 
620
 
 
621
Name ::= OCTET STRING(SIZE(2)) 
 
622
 
 
623
PkgdName ::= OCTET STRING(SIZE(4)) 
 
624
-- represents Package Name (2 octets) plus Property Name (2 octets) 
 
625
-- To wildcard a package use 0xFFFF for first two octets, choose 
 
626
-- is not allowed. To reference native property tag specified in 
 
627
-- Annex C, use 0x0000 as first two octets. 
 
628
-- Wildcarding of Package Name is permitted only if Property Name is 
 
629
-- also wildcarded. 
 
630
 
 
631
Relation ::= ENUMERATED 
 
632
 
633
        greaterThan(0), 
 
634
        smallerThan(1), 
 
635
        unequalTo(2), 
 
636
        ... 
 
637
 
638
 
 
639
LocalRemoteDescriptor ::= SEQUENCE 
 
640
 
641
        propGrps                SEQUENCE OF PropertyGroup, 
 
642
        ... 
 
643
 
644
 
 
645
PropertyGroup ::= SEQUENCE OF PropertyParm 
 
646
 
 
647
TerminationStateDescriptor ::= SEQUENCE  
 
648
 
649
        propertyParms           SEQUENCE OF PropertyParm, 
 
650
        eventBufferControl      EventBufferControl OPTIONAL, 
 
651
        serviceState            ServiceState OPTIONAL, 
 
652
        ... 
 
653
 
654
 
 
655
EventBufferControl ::= ENUMERATED 
 
656
 
657
        off(0), 
 
658
        lockStep(1), 
 
659
        ... 
 
660
 
661
 
 
662
ServiceState ::= ENUMERATED 
 
663
 
664
        test(0), 
 
665
        outOfSvc(1), 
 
666
        inSvc(2), 
 
667
         ... 
 
668
 
669
 
 
670
MuxDescriptor   ::= SEQUENCE 
 
671
 
672
        muxType                 MuxType, 
 
673
        termList                SEQUENCE OF TerminationID, 
 
674
--      nonStandardData         NonStandardData OPTIONAL, 
 
675
        ... 
 
676
 
677
 
 
678
MuxType ::= ENUMERATED 
 
679
 
680
        h221(0), 
 
681
        h223(1), 
 
682
        h226(2), 
 
683
        v76(3), 
 
684
        ... 
 
685
 
686
 
 
687
StreamID ::= INTEGER(0..65535)  -- 16 bit unsigned integer 
 
688
 
 
689
EventsDescriptor ::= SEQUENCE 
 
690
 
691
        requestID               RequestID, 
 
692
        eventList               SEQUENCE OF RequestedEvent, 
 
693
        ... 
 
694
 
695
 
 
696
RequestedEvent ::= SEQUENCE 
 
697
 
698
        pkgdName                PkgdName, 
 
699
        streamID                StreamID OPTIONAL, 
 
700
        eventAction             RequestedActions OPTIONAL, 
 
701
        evParList               SEQUENCE OF EventParameter, 
 
702
        ... 
 
703
 
704
 
 
705
RequestedActions ::= SEQUENCE 
 
706
 
707
        keepActive              BOOLEAN, 
 
708
        eventDM                 EventDM OPTIONAL, 
 
709
        secondEvent             SecondEventsDescriptor OPTIONAL, 
 
710
        signalsDescriptor       SignalsDescriptor OPTIONAL, 
 
711
        ... 
 
712
 
713
 
 
714
 
 
715
EventDM ::= CHOICE 
 
716
{
 
717
        digitMapName            DigitMapName, 
 
718
        digitMapValue           DigitMapValue 
 
719
 
720
 
 
721
SecondEventsDescriptor ::= SEQUENCE 
 
722
 
723
        requestID               RequestID, 
 
724
        eventList               SEQUENCE OF SecondRequestedEvent, 
 
725
        ... 
 
726
 
727
 
 
728
SecondRequestedEvent ::= SEQUENCE 
 
729
 
730
        pkgdName                PkgdName, 
 
731
        streamID                StreamID OPTIONAL, 
 
732
        eventAction             SecondRequestedActions OPTIONAL, 
 
733
        evParList               SEQUENCE OF EventParameter, 
 
734
        ... 
 
735
 
736
 
 
737
SecondRequestedActions ::= SEQUENCE 
 
738
 
739
        keepActive              BOOLEAN, 
 
740
        eventDM                 EventDM OPTIONAL, 
 
741
        signalsDescriptor       SignalsDescriptor OPTIONAL, 
 
742
        ... 
 
743
 
744
 
 
745
EventBufferDescriptor ::= SEQUENCE OF EventSpec 
 
746
 
 
747
EventSpec ::= SEQUENCE 
 
748
 
749
        eventName               EventName, 
 
750
        streamID                StreamID OPTIONAL, 
 
751
        eventParList            SEQUENCE OF EventParameter, 
 
752
        ... 
 
753
 
754
 
 
755
SignalsDescriptor ::= SEQUENCE OF SignalRequest 
 
756
 
 
757
SignalRequest ::= CHOICE 
 
758
 
759
        signal                  Signal, 
 
760
        seqSigList              SeqSigList, 
 
761
        ... 
 
762
 
763
 
 
764
SeqSigList ::= SEQUENCE 
 
765
 
766
        id                      INTEGER(0..65535), 
 
767
        signalList              SEQUENCE OF Signal 
 
768
 
769
 
 
770
Signal ::= SEQUENCE 
 
771
 
772
        signalName              SignalName, 
 
773
        streamID                StreamID OPTIONAL, 
 
774
        sigType                 SignalType OPTIONAL, 
 
775
        duration                INTEGER (0..65535) OPTIONAL, 
 
776
        notifyCompletion        NotifyCompletion OPTIONAL, 
 
777
        keepActive              BOOLEAN OPTIONAL, 
 
778
        sigParList              SEQUENCE OF SigParameter, 
 
779
        ... 
 
780
 
781
 
 
782
SignalType ::= ENUMERATED 
 
783
 
784
        brief(0), 
 
785
        onOff(1), 
 
786
        timeOut(2), 
 
787
        ... 
 
788
 
789
 
 
790
SignalName ::= PkgdName 
 
791
 
 
792
NotifyCompletion ::= BIT STRING 
 
793
 
794
        onTimeOut(0),
 
795
        onInterruptByEvent(1), 
 
796
        onInterruptByNewSignalDescr(2),
 
797
        otherReason(3) 
 
798
 
799
 
 
800
SigParameter ::= SEQUENCE 
 
801
 
802
        sigParameterName        Name, 
 
803
        value                   Value 
 
804
 
805
 
 
806
RequestID ::= INTEGER(0..4294967295)   -- 32 bit unsigned integer 
 
807
 
 
808
ModemDescriptor ::= SEQUENCE 
 
809
 
810
        mtl                     SEQUENCE OF ModemType,  
 
811
        mpl                     SEQUENCE OF PropertyParm 
 
812
--      nonStandardData         NonStandardData OPTIONAL 
 
813
 
814
 
 
815
ModemType ::= ENUMERATED 
 
816
 
817
        v18(0), 
 
818
        v22(1), 
 
819
        v22bis(2), 
 
820
        v32(3), 
 
821
        v32bis(4), 
 
822
        v34(5), 
 
823
        v90(6), 
 
824
        v91(7), 
 
825
        synchISDN(8), 
 
826
        ... 
 
827
 
828
 
 
829
DigitMapDescriptor ::= SEQUENCE 
 
830
 
831
        digitMapName            DigitMapName    OPTIONAL, 
 
832
        digitMapValue           DigitMapValue   OPTIONAL 
 
833
 
834
 
 
835
DigitMapName ::= Name 
 
836
 
 
837
DigitMapValue ::= SEQUENCE 
 
838
 
839
        startTimer              INTEGER(0..99) OPTIONAL, 
 
840
        shortTimer              INTEGER(0..99) OPTIONAL, 
 
841
        longTimer               INTEGER(0..99) OPTIONAL, 
 
842
        digitMapBody            IA5String, 
 
843
        -- See Section A.3 for explanation of digit map syntax 
 
844
        ... 
 
845
 
846
 
 
847
ServiceChangeParm ::= SEQUENCE 
 
848
 
849
        serviceChangeMethod     ServiceChangeMethod, 
 
850
        serviceChangeAddress    ServiceChangeAddress OPTIONAL, 
 
851
        serviceChangeVersion    INTEGER(0..99) OPTIONAL, 
 
852
        serviceChangeProfile    ServiceChangeProfile OPTIONAL, 
 
853
        serviceChangeReason     Value, 
 
854
        serviceChangeDelay      INTEGER(0..4294967295) OPTIONAL, 
 
855
                                    -- 32 bit unsigned integer 
 
856
        serviceChangeMgcId      MId OPTIONAL, 
 
857
        timeStamp               TimeNotation OPTIONAL, 
 
858
--      nonStandardData         NonStandardData OPTIONAL, 
 
859
        ... 
 
860
 
861
 
 
862
ServiceChangeAddress ::= CHOICE 
 
863
 
864
        portNumber              INTEGER(0..65535), -- TCP/UDP port number 
 
865
        ip4Address              IP4Address, 
 
866
        ip6Address              IP6Address, 
 
867
        domainName              DomainName, 
 
868
        deviceName              PathName, 
 
869
        mtpAddress              OCTET STRING(SIZE(2)), 
 
870
        ... 
 
871
 
872
 
 
873
ServiceChangeResParm ::= SEQUENCE 
 
874
 
875
        serviceChangeMgcId      MId OPTIONAL, 
 
876
        serviceChangeAddress    ServiceChangeAddress OPTIONAL, 
 
877
        serviceChangeVersion    INTEGER(0..99) OPTIONAL, 
 
878
        serviceChangeProfile    ServiceChangeProfile OPTIONAL, 
 
879
        ... 
 
880
 
881
 
 
882
ServiceChangeMethod ::= ENUMERATED 
 
883
 
884
        failover(0), 
 
885
        forced(1), 
 
886
        graceful(2), 
 
887
        restart(3), 
 
888
        disconnected(4), 
 
889
        handOff(5), 
 
890
        ... 
 
891
 
892
 
 
893
ServiceChangeProfile ::= SEQUENCE 
 
894
 
895
        profileName             Name, 
 
896
        version                 INTEGER(0..99) 
 
897
 
898
 
 
899
PackagesDescriptor ::= SEQUENCE OF PackagesItem 
 
900
 
 
901
PackagesItem ::= SEQUENCE 
 
902
 
903
        packageName             Name, 
 
904
        packageVersion          INTEGER(0..99), 
 
905
        ... 
 
906
 
907
 
 
908
StatisticsDescriptor ::= SEQUENCE OF StatisticsParameter 
 
909
 
 
910
StatisticsParameter ::= SEQUENCE 
 
911
 
912
        statName                PkgdName, 
 
913
        statValue               Value 
 
914
 
915
 
 
916
-- NonStandardData ::= SEQUENCE 
 
917
-- { 
 
918
--         nonStandardIdentifier   NonStandardIdentifier, 
 
919
--         data                    OCTET STRING 
 
920
-- } 
 
921
-- 
 
922
-- NonStandardIdentifier                ::= CHOICE 
 
923
-- { 
 
924
--         object                  OBJECT IDENTIFIER, 
 
925
--         h221NonStandard         H221NonStandard, 
 
926
--         experimental            IA5String(SIZE(8)),  
 
927
--  first two characters should be "X-" or "X+" 
 
928
--         ... 
 
929
-- } 
 
930
--  
 
931
-- H221NonStandard ::= SEQUENCE 
 
932
-- {
 
933
--         t35CountryCode1         INTEGER(0..255), 
 
934
--         t35CountryCode2         INTEGER(0..255),    country, as per T.35 
 
935
--         t35Extension            INTEGER(0..255),    assigned nationally 
 
936
--         manufacturerCode        INTEGER(0..65535),  assigned nationally 
 
937
--         ... 
 
938
-- } 
 
939
 
 
940
TimeNotation ::= SEQUENCE 
 
941
 
942
        date                    IA5String(SIZE(8)), -- yyyymmdd format 
 
943
        time                    IA5String(SIZE(8))  -- hhmmssss format 
 
944
 
945
 
 
946
Value ::= OCTET STRING 
 
947
 
 
948
 
 
949
END 
 
950