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

« back to all changes in this revision

Viewing changes to lib/megaco/include/megaco_sdp.hrl

  • 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:
21
21
%%
22
22
%%
23
23
%% Explanaition of the fields in the SDP body
24
 
%%   (See RFC 2327 for the complete decription)
 
24
%%   (See RFC 2327 and RFC 3266 for the complete decription)
25
25
%%
26
26
%% Session descriptions
27
27
%%
62
62
%%
63
63
%% FieldID    FieldValue
64
64
%% 
65
 
%% o          #sdp_o{}
66
 
%% c          #sdp_c{}
67
 
%% m          #sdp_m{}
68
 
%% a          #sdp_a_rtpmap{}  iff 'att-field'=rtpmap
69
 
%% a          #sdp_a_ptime{}   iff 'att-field'=ptime
 
65
%% o          #megaco_sdp_o{}
 
66
%% c          #megaco_sdp_c{}
 
67
%% m          #megaco_sdp_m{}
 
68
%% a          #megaco_sdp_a_rtpmap{}  iff 'att-field'=rtpmap
 
69
%% a          #megaco_sdp_a_ptime{}   iff 'att-field'=ptime
70
70
%% <other>    string()
71
71
%%
 
72
%% An example SDP description is:
 
73
%%
 
74
%%      v=0
 
75
%%      o=mhandley 2890844526 2890842807 IN IP4 126.16.64.4
 
76
%%      s=SDP Seminar
 
77
%%      i=A Seminar on the session description protocol
 
78
%%      u=http://www.cs.ucl.ac.uk/staff/M.Handley/sdp.03.ps
 
79
%%      e=mjh@isi.edu (Mark Handley)
 
80
%%      c=IN IP4 224.2.17.12/127
 
81
%%      t=2873397496 2873404696
 
82
%%      a=recvonly
 
83
%%      m=audio 49170 RTP/AVP 0
 
84
%%      m=video 51372 RTP/AVP 31
 
85
%%      m=application 32416 udp wb
 
86
%%      a=orient:portrait
 
87
%% 
 
88
%% 
 
89
%% An example SDP description with IPv6 addresses
 
90
%%
 
91
%%    v=0
 
92
%%    o=nasa1 971731711378798081 0 IN IP6 2201:056D::112E:144A:1E24
 
93
%%    s=(Almost) live video feed from Mars-II satellite
 
94
%%    p=+1 713 555 1234
 
95
%%    c=IN IP6 FF1E:03AD::7F2E:172A:1E24
 
96
%%    t=3338481189 3370017201
 
97
%%    m=audio 6000 RTP/AVP 2
 
98
%%    a=rtpmap:2 G726-32/8000
 
99
%%    m=video 6024 RTP/AVP 107
 
100
%%    a=rtpmap:107 H263-1998/90000
 
101
%% 
72
102
%%----------------------------------------------------------------------
73
 
-ifndef(sdp_).
74
 
-define(sdp_, true).
75
 
 
76
 
 
77
 
-record(sdp_v, {
 
103
 
 
104
-ifndef(megaco_sdp_).
 
105
-define(megaco_sdp_, true).
 
106
 
 
107
 
 
108
%% ===================================================================
 
109
%% 
 
110
%% Protocol Version
 
111
%% 
 
112
%% v=0
 
113
%% 
 
114
%% This field gives the version of the Session Description Protocol.
 
115
%% There is no minor version number.
 
116
%% 
 
117
 
 
118
-record(megaco_sdp_v, {
78
119
          version                                       % integer()
 
120
         }
 
121
       ).
 
122
 
 
123
 
 
124
 
 
125
 
 
126
%% ===================================================================
 
127
%% 
 
128
%% Origin
 
129
%%
 
130
%% o=<username> <session id> <version> <network type> <address type>
 
131
%% <address>
 
132
%%
 
133
%% The "o=" field gives the originator of the session (their username
 
134
%% and the address of the user's host) plus a session id and session
 
135
%% version number.
 
136
%%
 
137
%% <username> is the user's login on the originating host, or it is
 
138
%% "-" if the originating host does not support the concept of user
 
139
%% ids.  <username> must not contain spaces.  <session id> is a
 
140
%% numeric string such that the tuple of <username>, <session id>,
 
141
%% <network type>, <address type> and <address> form a globally unique
 
142
%% identifier for the session.
 
143
%%
 
144
%% The method of <session id> allocation is up to the creating tool,
 
145
%% but it has been suggested that a Network Time Protocol (NTP)
 
146
%% timestamp be used to ensure uniqueness [1].
 
147
%%
 
148
%% <version> is a version number for this announcement.  It is needed
 
149
%% for proxy announcements to detect which of several announcements
 
150
%% for the same session is the most recent.  Again its usage is up to
 
151
%% the creating tool, so long as <version> is increased when a
 
152
%% modification is made to the session data.  Again, it is recommended
 
153
%% (but not mandatory) that an NTP timestamp is used.
 
154
%%
 
155
%% <network type> is a text string giving the type of network.
 
156
%% Initially "IN" is defined to have the meaning "Internet".  
 
157
%% 
 
158
%% <address type> is a text string giving the type of the address 
 
159
%% that follows. Initially "IP4" and "IP6" are defined.  
 
160
%% 
 
161
%% <address> is the globally unique address of the machine from which
 
162
%% the session was created.  For an address type of IP4, this is
 
163
%% either the fully-qualified domain name of the machine, or the
 
164
%% dotted-decimal representation of the IP version 4 address of the
 
165
%% machine.  For an address type of IP6, this is either the
 
166
%% fully-qualified domain name of the machine, or the compressed
 
167
%% textual representation of the IP version 6 address of the machine.
 
168
%% For both IP4 and IP6, the fully-qualified domain name is the form
 
169
%% that SHOULD be given unless this is unavailable, in which case the
 
170
%% globally unique address may be substituted.  A local IP address
 
171
%% MUST NOT be used in any context where the SDP description might
 
172
%% leave the scope in which the address is meaningful.
 
173
%%
 
174
%% In general, the "o=" field serves as a globally unique identifier
 
175
%% for this version of this session description, and the subfields
 
176
%% excepting the version taken together identify the session
 
177
%% irrespective of any modifications.
 
178
%% 
 
179
 
 
180
-record(megaco_sdp_o, {
 
181
          user_name,          % string()
 
182
          session_id,         % integer()
 
183
          version,            % integer()
 
184
          network_type = in,  % in | string()
 
185
          address_type = ip4, % ip4 | ip6 | string()
 
186
          address             % string()
 
187
         }
 
188
       ).
 
189
 
 
190
 
 
191
 
 
192
 
 
193
%% ===================================================================
 
194
%% 
 
195
%% Session Name
 
196
%%
 
197
%% s=<session name>
 
198
%%
 
199
%% The "s=" field is the session name.  There must be one and only one
 
200
%% "s=" field per session description, and it must contain ISO 10646
 
201
%% characters.
 
202
%% 
 
203
 
 
204
-record(megaco_sdp_s, {
 
205
          name                                  % string()
 
206
         }
 
207
       ).
 
208
 
 
209
 
 
210
 
 
211
 
 
212
%% ===================================================================
 
213
%% 
 
214
%% Session and Media Information
 
215
%%
 
216
%% i=<session description>
 
217
%%
 
218
%% The "i=" field is information about the session.  There may be at
 
219
%% most one session-level "i=" field per session description, and at
 
220
%% most one "i=" field per media. Although it may be omitted, this is
 
221
%% discouraged for session announcements, and user interfaces for
 
222
%% composing sessions should require text to be entered.  If it is
 
223
%% present it must contain ISO 10646 characters.
 
224
%%
 
225
%% A single "i=" field can also be used for each media definition.  In
 
226
%% media definitions, "i=" fields are primarily intended for labeling
 
227
%% media streams. As such, they are most likely to be useful when a
 
228
%% single session has more than one distinct media stream of the same
 
229
%% media type.  An example would be two different whiteboards, one for
 
230
%% slides and one for feedback and questions.
 
231
%% 
 
232
 
 
233
-record(megaco_sdp_i, {
 
234
          session_descriptor                    % string()
 
235
         }
 
236
       ).
 
237
 
 
238
 
 
239
 
 
240
 
 
241
%% ===================================================================
 
242
%% 
 
243
%% URI
 
244
%%
 
245
%% u=<URI>
 
246
%%
 
247
%% o A URI is a Universal Resource Identifier as used by WWW clients
 
248
%%
 
249
%% o The URI should be a pointer to additional information about the
 
250
%%   conference
 
251
%%
 
252
%% o This field is optional, but if it is present it should be specified
 
253
%%   before the first media field
 
254
%%
 
255
%% o No more than one URI field is allowed per session description
 
256
%% 
 
257
 
 
258
-record(megaco_sdp_u, {
 
259
          uri                                   % string()
 
260
         }
 
261
       ).
 
262
 
 
263
 
 
264
 
 
265
 
 
266
%% ===================================================================
 
267
%% 
 
268
%% Email Address and Phone Number
 
269
%%
 
270
%% e=<email address>
 
271
%% p=<phone number>
 
272
%%
 
273
%% o These specify contact information for the person responsible for
 
274
%%   the conference.  This is not necessarily the same person that
 
275
%%   created the conference announcement.
 
276
%%
 
277
%% o Either an email field or a phone field must be specified.
 
278
%%   Additional email and phone fields are allowed.
 
279
%%
 
280
%% o If these are present, they should be specified before the first
 
281
%%   media field.
 
282
%%
 
283
%% o More than one email or phone field can be given for a session
 
284
%%   description.
 
285
%%
 
286
%% o Phone numbers should be given in the conventional international
 
287
%%   format - preceded by a "+ and the international country code.
 
288
%%   There must be a space or a hyphen ("-") between the country code
 
289
%%   and the rest of the phone number.  Spaces and hyphens may be used
 
290
%%   to split up a phone field to aid readability if desired. For
 
291
%%   example:
 
292
%%
 
293
%%                 p=+44-171-380-7777 or p=+1 617 253 6011
 
294
%%
 
295
%% o Both email addresses and phone numbers can have an optional free
 
296
%%   text string associated with them, normally giving the name of the
 
297
%%   person who may be contacted.  This should be enclosed in
 
298
%%   parenthesis if it is present.  For example:
 
299
%%
 
300
%%                      e=mjh@isi.edu (Mark Handley)
 
301
%%
 
302
%%   The alternative RFC822 name quoting convention is also allowed for
 
303
%%   both email addresses and phone numbers.  For example,
 
304
%%
 
305
%%                      e=Mark Handley <mjh@isi.edu>
 
306
%%
 
307
%%   The free text string should be in the ISO-10646 character set with
 
308
%%   UTF-8 encoding, or alternatively in ISO-8859-1 or other encodings
 
309
%%   if the appropriate charset session-level attribute is set.
 
310
%% 
 
311
 
 
312
-record(megaco_sdp_e, {
 
313
          email                                 % string()
 
314
         }
 
315
       ).
 
316
 
 
317
-record(megaco_sdp_p, {
 
318
          phone_number                          % string()
 
319
         }
 
320
       ).
 
321
 
 
322
 
 
323
 
 
324
 
 
325
%% ===================================================================
 
326
%% 
 
327
%% Connection Data
 
328
%% 
 
329
%% c=<network type> <address type> <connection address>
 
330
%%
 
331
%% The "c=" field contains connection data.
 
332
%%
 
333
%% A session announcement must contain one "c=" field in each media
 
334
%% description (see below) or a "c=" field at the session-level.  It may
 
335
%% contain a session-level "c=" field and one additional "c=" field per
 
336
%% media description, in which case the per-media values override the
 
337
%% session-level settings for the relevant media.
 
338
%%
 
339
%% The first sub-field is the network type, which is a text string
 
340
%% giving the type of network.  Initially "IN" is defined to have the
 
341
%% meaning "Internet".
 
342
%%
 
343
%% The second sub-field is the address type.  This allows SDP to be used
 
344
%% for sessions that are not IP based.  Currently only IP4 is defined.
 
345
%%
 
346
%% The third sub-field is the connection address.  Optional extra
 
347
%% subfields may be added after the connection address depending on the
 
348
%% value of the <address type> field.
 
349
%%
 
350
%% For IP4 addresses, the connection address is defined as follows:
 
351
%%
 
352
%% o Typically the connection address will be a class-D IP multicast
 
353
%%   group address.  If the session is not multicast, then the
 
354
%%   connection address contains the fully-qualified domain name or the
 
355
%%   unicast IP address of the expected data source or data relay or
 
356
%%   data sink as determined by additional attribute fields. It is not
 
357
%%   expected that fully-qualified domain names or unicast addresses
 
358
%%   will be given in a session description that is communicated by a
 
359
%%   multicast announcement, though this is not prohibited.  If a
 
360
%%   unicast data stream is to pass through a network address
 
361
%%   translator, the use of a fully-qualified domain name rather than an
 
362
%%   unicast IP address is RECOMMENDED.  In other cases, the use of an
 
363
%%   IP address to specify a particular interface on a multi-homed host
 
364
%%   might be required.  Thus this specification leaves the decision as
 
365
%%   to which to use up to the individual application, but all
 
366
%%   applications MUST be able to cope with receiving both formats.
 
367
%% 
 
368
%% o Conferences using an IP multicast connection address must also have
 
369
%%   a time to live (TTL) value present in addition to the multicast
 
370
%%   address.  The TTL and the address together define the scope with
 
371
%%   which multicast packets sent in this conference will be sent. TTL
 
372
%%   values must be in the range 0-255.
 
373
%%
 
374
%%   The TTL for the session is appended to the address using a slash as
 
375
%%   a separator.  An example is:
 
376
%%
 
377
%%                         c=IN IP4 224.2.1.1/127
 
378
%%
 
379
%%   Hierarchical or layered encoding schemes are data streams where the
 
380
%%   encoding from a single media source is split into a number of
 
381
%%   layers.  The receiver can choose the desired quality (and hence
 
382
%%   bandwidth) by only subscribing to a subset of these layers.  Such
 
383
%%   layered encodings are normally transmitted in multiple multicast
 
384
%%   groups to allow multicast pruning.  This technique keeps unwanted
 
385
%%   traffic from sites only requiring certain levels of the hierarchy.
 
386
%%   For applications requiring multiple multicast groups, we allow the
 
387
%%   following notation to be used for the connection address:
 
388
%%
 
389
%%          <base multicast address>/<ttl>/<number of addresses>
 
390
%%
 
391
%%   If the number of addresses is not given it is assumed to be one.
 
392
%%   Multicast addresses so assigned are contiguously allocated above
 
393
%%   the base address, so that, for example:
 
394
%%
 
395
%%                        c=IN IP4 224.2.1.1/127/3
 
396
%%
 
397
%%   would state that addresses 224.2.1.1, 224.2.1.2 and 224.2.1.3 are
 
398
%%   to be used at a ttl of 127.  This is semantically identical to
 
399
%%   including multiple "c=" lines in a media description:
 
400
%%
 
401
%%                         c=IN IP4 224.2.1.1/127
 
402
%%                         c=IN IP4 224.2.1.2/127
 
403
%%                         c=IN IP4 224.2.1.3/127
 
404
%%
 
405
%%   Multiple addresses or "c=" lines can only be specified on a per-
 
406
%%   media basis, and not for a session-level "c=" field.
 
407
%%
 
408
%%   It is illegal for the slash notation described above to be used for
 
409
%%   IP unicast addresses.
 
410
%% 
 
411
 
 
412
-record(megaco_sdp_c, {
 
413
          network_type = in,                    % in | string()
 
414
          address_type = ip4,                   % ip4 | ip6 | string()
 
415
          connection_addr                       % string() | #conn_addr{}
 
416
         }).
 
417
 
 
418
%% Only if address type = ip4
 
419
-record(megaco_sdp_c_conn_addr, {
 
420
          base,                                 % string()
 
421
          ttl,                                  % integer()
 
422
          num_of                                % undefined | integer()
79
423
         }).
80
424
 
81
 
-record(sdp_o, {
82
 
          user_name,                            % string()
83
 
          session_id,                           % string()
84
 
          version,                              % string()
85
 
          network_type,                         % string()
86
 
          address_type,                         % string()
87
 
          address                               % string()
88
 
         }).
89
 
          
90
 
-record(sdp_c, {
91
 
          network_type,                         % string()
92
 
          address_type,                         % string()
93
 
          connection_addr                       % string() | 
94
 
                                                % {multicast, string(), 
95
 
                                                %  ttl-integer(), params-[]}
96
 
         }).
97
 
 
98
 
-record(sdp_m, {
99
 
          media,                                % string()
100
 
          port,                                 % integer()
101
 
          num_ports,                            % integer()
102
 
          transport,                            % string()
103
 
          fmt_list = []                         % [ string() ]
104
 
         }).
105
 
 
106
 
-record(sdp_b, {
 
425
 
 
426
 
 
427
%% ===================================================================
 
428
%% 
 
429
%% Bandwidth
 
430
%%
 
431
%% b=<modifier>:<bandwidth-value>
 
432
%%
 
433
%% o This specifies the proposed bandwidth to be used by the session or
 
434
%%   media, and is optional.
 
435
%%
 
436
%% o <bandwidth-value> is in kilobits per second
 
437
%%
 
438
%% o <modifier> is a single alphanumeric word giving the meaning of the
 
439
%%   bandwidth figure.
 
440
%%
 
441
%% o Two modifiers are initially defined:
 
442
%%
 
443
%% CT Conference Total: An implicit maximum bandwidth is associated with
 
444
%%   each TTL on the Mbone or within a particular multicast
 
445
%%   administrative scope region (the Mbone bandwidth vs. TTL limits are
 
446
%%   given in the MBone FAQ). If the bandwidth of a session or media in
 
447
%%   a session is different from the bandwidth implicit from the scope,
 
448
%%   a `b=CT:...' line should be supplied for the session giving the
 
449
%%   proposed upper limit to the bandwidth used. The primary purpose of
 
450
%%   this is to give an approximate idea as to whether two or more
 
451
%%   conferences can co-exist simultaneously.
 
452
%%
 
453
%% AS Application-Specific Maximum: The bandwidth is interpreted to be
 
454
%%   application-specific, i.e., will be the application's concept of
 
455
%%   maximum bandwidth.  Normally this will coincide with what is set on
 
456
%%   the application's "maximum bandwidth" control if applicable.
 
457
%%
 
458
%%   Note that CT gives a total bandwidth figure for all the media at
 
459
%%   all sites.  AS gives a bandwidth figure for a single media at a
 
460
%%   single site, although there may be many sites sending
 
461
%%   simultaneously.
 
462
%%
 
463
%% o Extension Mechanism: Tool writers can define experimental bandwidth
 
464
%%   modifiers by prefixing their modifier with "X-". For example:
 
465
%%
 
466
%%                               b=X-YZ:128
 
467
%%
 
468
%%   SDP parsers should ignore bandwidth fields with unknown modifiers.
 
469
%%   Modifiers should be alpha-numeric and, although no length limit is
 
470
%%   given, they are recommended to be short.
 
471
%% 
 
472
 
 
473
-record(megaco_sdp_b, {
107
474
          modifier,                             % string()
108
475
          bandwidth                             % integer()
109
476
         }).
110
477
 
111
 
-record(sdp_t, {
 
478
 
 
479
 
 
480
 
 
481
%% ===================================================================
 
482
%% 
 
483
%% Times, Repeat Times and Time Zones
 
484
%%
 
485
%% t=<start time>  <stop time>
 
486
%% r=<repeat interval> <active duration> <list of offsets from start-time>
 
487
%% z=<adjustment time> <offset> <adjustment time> <offset> ....
 
488
%%
 
489
%% o "t=" fields specify the start and stop times for a conference
 
490
%%   session.  Multiple "t=" fields may be used if a session is active
 
491
%%   at multiple irregularly spaced times; each additional "t=" field
 
492
%%   specifies an additional period of time for which the session will
 
493
%%   be active.  If the session is active at regular times, an "r="
 
494
%%   field (see below) should be used in addition to and following a
 
495
%%   "t=" field - in which case the "t=" field specifies the start and
 
496
%%   stop times of the repeat sequence.
 
497
%%
 
498
%% o The first and second sub-fields give the start and stop times for
 
499
%%   the conference respectively.  These values are the decimal
 
500
%%   representation of Network Time Protocol (NTP) time values in
 
501
%%   seconds [1].  To convert these values to UNIX time, subtract
 
502
%%   decimal 2208988800.
 
503
%%
 
504
%% o If the stop-time is set to zero, then the session is not bounded,
 
505
%%   though it will not become active until after the start-time.  If
 
506
%%   the start-time is also zero, the session is regarded as
 
507
%%   permanent.
 
508
%%
 
509
%%   User interfaces should strongly discourage the creation of
 
510
%%   unbounded and permanent sessions as they give no information
 
511
%%   about when the session is actually going to terminate, and so
 
512
%%   make scheduling difficult.
 
513
%%
 
514
%%   The general assumption may be made, when displaying unbounded
 
515
%%   sessions that have not timed out to the user, that an unbounded
 
516
%%   session will only be active until half an hour from the current
 
517
%%   time or the session start time, whichever is the later.  If
 
518
%%   behaviour other than this is required, an end-time should be
 
519
%%   given and modified as appropriate when new information becomes
 
520
%%   available about when the session should really end.
 
521
%%
 
522
%%   Permanent sessions may be shown to the user as never being active
 
523
%%   unless there are associated repeat times which state precisely
 
524
%%   when the session will be active.  In general, permanent sessions
 
525
%%   should not be created for any session expected to have a duration
 
526
%%   of less than 2 months, and should be discouraged for sessions
 
527
%%   expected to have a duration of less than 6 months.
 
528
%%
 
529
%% o "r=" fields specify repeat times for a session.  For example, if
 
530
%%   a session is active at 10am on Monday and 11am on Tuesday for one
 
531
%%   hour each week for three months, then the <start time> in the
 
532
%%   corresponding "t=" field would be the NTP representation of 10am
 
533
%%   on the first Monday, the <repeat interval> would be 1 week, the
 
534
%%   <active duration> would be 1 hour, and the offsets would be zero
 
535
%%   and 25 hours. The corresponding "t=" field stop time would be the
 
536
%%   NTP representation of the end of the last session three months
 
537
%%   later. By default all fields are in seconds, so the "r=" and "t="
 
538
%%   fields might be:
 
539
%%
 
540
%%                         t=3034423619 3042462419
 
541
%%                          r=604800 3600 0 90000
 
542
%%
 
543
%%   To make announcements more compact, times may also be given in
 
544
%%   units of days, hours or minutes. The syntax for these is a number
 
545
%%   immediately followed by a single case-sensitive character.
 
546
%%   Fractional units are not allowed - a smaller unit should be used
 
547
%%   instead.  The following unit specification characters are
 
548
%%   allowed:
 
549
%%
 
550
%%                       d - days (86400 seconds)
 
551
%%                      h - minutes (3600 seconds)
 
552
%%                       m - minutes (60 seconds)
 
553
%%       s - seconds (allowed for completeness but not recommended)
 
554
%%
 
555
%%   Thus, the above announcement could also have been written:
 
556
%%
 
557
%%                             r=7d 1h 0 25h
 
558
%%
 
559
%%   Monthly and yearly repeats cannot currently be directly specified
 
560
%%   with a single SDP repeat time - instead separate "t" fields
 
561
%%   should be used to explicitly list the session times.
 
562
%% 
 
563
%%   To schedule a repeated session which spans a change from
 
564
%%   daylight- saving time to standard time or vice-versa, it is
 
565
%%   necessary to specify offsets from the base repeat times. This is
 
566
%%   required because different time zones change time at different
 
567
%%   times of day, different countries change to or from daylight time
 
568
%%   on different dates, and some countries do not have daylight
 
569
%%   saving time at all.
 
570
%%
 
571
%%   Thus in order to schedule a session that is at the same time
 
572
%%   winter and summer, it must be possible to specify unambiguously
 
573
%%   by whose time zone a session is scheduled.  To simplify this task
 
574
%%   for receivers, we allow the sender to specify the NTP time that a
 
575
%%   time zone adjustment happens and the offset from the time when
 
576
%%   the session was first scheduled.  The "z" field allows the sender
 
577
%%   to specify a list of these adjustment times and offsets from the
 
578
%%   base time.
 
579
%%
 
580
%%   An example might be:
 
581
%%
 
582
%%                      z=2882844526 -1h 2898848070 0
 
583
%%
 
584
%%   This specifies that at time 2882844526 the time base by which the
 
585
%%   session's repeat times are calculated is shifted back by 1 hour,
 
586
%%   and that at time 2898848070 the session's original time base is
 
587
%%   restored. Adjustments are always relative to the specified start
 
588
%%   time - they are not cumulative.
 
589
%%
 
590
%% o If a session is likely to last several years, it is expected that
 
591
%%   the session announcement will be modified periodically rather
 
592
%%   than transmit several years worth of adjustments in one
 
593
%%   announcement.
 
594
%% 
 
595
 
 
596
-record(megaco_sdp_t, {
112
597
          start,                                % integer()
113
598
          stop                                  % integer()
114
599
         }).
115
600
 
116
 
-record(sdp_r, {
 
601
-record(megaco_sdp_r, {
117
602
          repeat_interval,                      % string()
118
603
          active_duration,                      % string()
119
604
          list_of_offsets                       % [ string() ]
120
 
         }).
 
605
         }
 
606
       ).
121
607
      
122
 
-record(sdp_z, {
 
608
-record(megaco_sdp_z, {
123
609
          list_of_adjustments                   % [ string() ]
124
 
         }).
125
 
 
126
 
-record(sdp_k, {
127
 
          method,                               % string()
128
 
          encryption_key                        % string()
129
 
         }).
130
 
 
131
 
-record(sdp_a, {
132
 
          attribute,                             % atom()
133
 
          value                                 % type depends on variable
134
 
         }).
135
 
 
136
 
-record(sdp_a_rtpmap, {
 
610
         }
 
611
       ).
 
612
 
 
613
 
 
614
 
 
615
 
 
616
%% ===================================================================
 
617
%% 
 
618
%% Encryption Keys
 
619
%% 
 
620
%% k=<method>
 
621
%% k=<method>:<encryption key>
 
622
%%
 
623
%% o The session description protocol may be used to convey encryption
 
624
%%   keys.  A key field is permitted before the first media entry (in
 
625
%%   which case it applies to all media in the session), or for each
 
626
%%   media entry as required.
 
627
%%
 
628
%% o The format of keys and their usage is outside the scope of this
 
629
%%   document, but see [3].
 
630
%%
 
631
%% o The method indicates the mechanism to be used to obtain a usable
 
632
%%   key by external means, or from the encoded encryption key given.
 
633
%%
 
634
%%   The following methods are defined:
 
635
%%
 
636
%%    k=clear:<encryption key>
 
637
%%      The encryption key (as described in [3] for  RTP  media  streams
 
638
%%      under  the  AV  profile)  is  included untransformed in this key
 
639
%%      field.
 
640
%%
 
641
%%    k=base64:<encoded encryption key>
 
642
%%      The encryption key (as described in [3] for RTP media streams
 
643
%%      under the AV profile) is included in this key field but has been
 
644
%%      base64 encoded because it includes characters that are
 
645
%%      prohibited in SDP.
 
646
%%
 
647
%%    k=uri:<URI to obtain key>
 
648
%%      A Universal Resource Identifier as used by WWW clients is
 
649
%%      included in this key field.  The URI refers to the data
 
650
%%      containing the key, and may require additional authentication
 
651
%%      before the key can be returned.  When a request is made to the
 
652
%%      given URI, the MIME content-type of the reply specifies the
 
653
%%      encoding for the key in the reply.  The key should not be
 
654
%%      obtained until the user wishes to join the session to reduce
 
655
%%      synchronisation of requests to the WWW server(s).
 
656
%%
 
657
%%    k=prompt
 
658
%%      No key is included in this SDP description, but the session or
 
659
%%      media stream referred to by this key field is encrypted.  The
 
660
%%      user should be prompted for the key when attempting to join the
 
661
%%      session, and this user-supplied key should then be used to
 
662
%%      decrypt the media streams.
 
663
%% 
 
664
 
 
665
-record(megaco_sdp_k, {
 
666
          method,            % clear | base64 | uri | prompt | string()
 
667
          encryption_key     % undefined | string()
 
668
         }
 
669
       ).
 
670
 
 
671
 
 
672
 
 
673
 
 
674
%% ===================================================================
 
675
%% 
 
676
%% Attributes
 
677
%% 
 
678
%% a=<attribute>
 
679
%% a=<attribute>:<value>
 
680
%%
 
681
%% Attributes are the primary means for extending SDP.  Attributes may
 
682
%% be defined to be used as "session-level" attributes, "media-level"
 
683
%% attributes, or both.
 
684
%%
 
685
%% A media description may have any number of attributes ("a=" fields)
 
686
%% which are media specific.  These are referred to as "media-level"
 
687
%% attributes and add information about the media stream.  Attribute
 
688
%% fields can also be added before the first media field; these
 
689
%% "session-level" attributes convey additional information that
 
690
%% applies to the conference as a whole rather than to individual
 
691
%% media; an example might be the conference's floor control policy.
 
692
%%
 
693
%% Attribute fields may be of two forms:
 
694
%%
 
695
%% o property attributes.  A property attribute is simply of the form
 
696
%%   "a=<flag>".  These are binary attributes, and the presence of the
 
697
%%   attribute conveys that the attribute is a property of the
 
698
%%   session.  An example might be "a=recvonly".
 
699
%%
 
700
%% o value attributes.  A value attribute is of the form
 
701
%%   "a=<attribute>:<value>".  An example might be that a whiteboard
 
702
%%   could have the value attribute "a=orient:landscape"
 
703
%%
 
704
%% Attribute interpretation depends on the media tool being invoked.
 
705
%% Thus receivers of session descriptions should be configurable in
 
706
%% their interpretation of announcements in general and of attributes
 
707
%% in particular.
 
708
%%
 
709
%% Attribute names must be in the US-ASCII subset of ISO-10646/UTF-8.
 
710
%%
 
711
%% Attribute values are byte strings, and MAY use any byte value
 
712
%% except 0x00 (Nul), 0x0A (LF), and 0x0D (CR). By default, attribute
 
713
%% values are to be interpreted as in ISO-10646 character set with
 
714
%% UTF-8 encoding.  Unlike other text fields, attribute values are NOT
 
715
%% normally affected by the `charset' attribute as this would make
 
716
%% comparisons against known values problematic.  However, when an
 
717
%% attribute is defined, it can be defined to be charset-dependent, in
 
718
%% which case it's value should be interpreted in the session charset
 
719
%% rather than in ISO-10646.
 
720
%%
 
721
%% Attributes that will be commonly used can be registered with IANA
 
722
%% (see Appendix B).  Unregistered attributes should begin with "X-"
 
723
%% to prevent inadvertent collision with registered attributes.  In
 
724
%% either case, if an attribute is received that is not understood, it
 
725
%% should simply be ignored by the receiver.
 
726
%% 
 
727
%% Suggested Attributes
 
728
%% 
 
729
%% The following attributes are suggested.  Since application writers
 
730
%% may add new attributes as they are required, this list is not
 
731
%% exhaustive.
 
732
%%
 
733
%% a=cat:<category>
 
734
%%   This attribute gives the dot-separated hierarchical category of
 
735
%%   the session.  This is to enable a receiver to filter unwanted
 
736
%%   sessions by category.  It would probably have been a compulsory
 
737
%%   separate field, except for its experimental nature at this time.
 
738
%%   It is a session-level attribute, and is not dependent on charset.
 
739
%%
 
740
%% a=keywds:<keywords>
 
741
%%   Like the cat attribute, this is to assist identifying wanted
 
742
%%   sessions at the receiver.  This allows a receiver to select
 
743
%%   interesting session based on keywords describing the purpose of
 
744
%%   the session.  It is a session-level attribute. It is a charset
 
745
%%   dependent attribute, meaning that its value should be interpreted
 
746
%%   in the charset specified for the session description if one is
 
747
%%   specified, or by default in ISO 10646/UTF-8.
 
748
%%
 
749
%% a=tool:<name and version of tool>
 
750
%%   This gives the name and version number of the tool used to create
 
751
%%   the session description.  It is a session-level attribute, and is
 
752
%%   not dependent on charset.
 
753
%%
 
754
%% a=ptime:<packet time>
 
755
%%   This gives the length of time in milliseconds represented by the
 
756
%%   media in a packet. This is probably only meaningful for audio
 
757
%%   data.  It should not be necessary to know ptime to decode RTP or
 
758
%%   vat audio, and it is intended as a recommendation for the
 
759
%%   encoding/packetisation of audio.  It is a media attribute, and is
 
760
%%   not dependent on charset.
 
761
%% 
 
762
%% a=recvonly
 
763
%%   This specifies that the tools should be started in receive-only
 
764
%%   mode where applicable. It can be either a session or media
 
765
%%   attribute, and is not dependent on charset.
 
766
%%
 
767
%% a=sendrecv
 
768
%%   This specifies that the tools should be started in send and
 
769
%%   receive mode.  This is necessary for interactive conferences with
 
770
%%   tools such as wb which defaults to receive only mode. It can be
 
771
%%   either a session or media attribute, and is not dependent on
 
772
%%   charset.
 
773
%%
 
774
%% a=sendonly
 
775
%%   This specifies that the tools should be started in send-only
 
776
%%   mode.  An example may be where a different unicast address is to
 
777
%%   be used for a traffic destination than for a traffic source. In
 
778
%%   such a case, two media descriptions may be use, one sendonly and
 
779
%%   one recvonly. It can be either a session or media attribute, but
 
780
%%   would normally only be used as a media attribute, and is not
 
781
%%   dependent on charset.
 
782
%%
 
783
%% a=orient:<whiteboard orientation>
 
784
%%   Normally this is only used in a whiteboard media specification.
 
785
%%   It specifies the orientation of a the whiteboard on the screen.
 
786
%%   It is a media attribute. Permitted values are `portrait',
 
787
%%   `landscape' and `seascape' (upside down landscape). It is not
 
788
%%   dependent on charset
 
789
%%
 
790
%% a=type:<conference type>
 
791
%%   This specifies the type of the conference.  Suggested values are
 
792
%%   `broadcast', `meeting', `moderated', `test' and `H332'.
 
793
%%   `recvonly' should be the default for `type:broadcast' sessions,
 
794
%%   `type:meeting' should imply `sendrecv' and `type:moderated'
 
795
%%   should indicate the use of a floor control tool and that the
 
796
%%   media tools are started so as to "mute" new sites joining the
 
797
%%   conference.
 
798
%%
 
799
%%   Specifying the attribute type:H332 indicates that this loosely
 
800
%%   coupled session is part of a H.332 session as defined in the ITU
 
801
%%   H.332 specification [10].  Media tools should be started
 
802
%%   `recvonly'.
 
803
%%
 
804
%%   Specifying the attribute type:test is suggested as a hint that,
 
805
%%   unless explicitly requested otherwise, receivers can safely avoid
 
806
%%   displaying this session description to users.
 
807
%%   
 
808
%%   The type attribute is a session-level attribute, and is not
 
809
%%   dependent on charset.
 
810
%% 
 
811
%% a=charset:<character set>
 
812
%%   This specifies the character set to be used to display the
 
813
%%   session name and information data.  By default, the ISO-10646
 
814
%%   character set in UTF-8 encoding is used. If a more compact
 
815
%%   representation is required, other character sets may be used such
 
816
%%   as ISO-8859-1 for Northern European languages.  In particular,
 
817
%%   the ISO 8859-1 is specified with the following SDP attribute:
 
818
%%   
 
819
%%                         a=charset:ISO-8859-1
 
820
%%   
 
821
%%   This is a session-level attribute; if this attribute is present,
 
822
%%   it must be before the first media field.  The charset specified
 
823
%%   MUST be one of those registered with IANA, such as ISO-8859-1.
 
824
%%   The character set identifier is a US-ASCII string and MUST be
 
825
%%   compared against the IANA identifiers using a case-insensitive
 
826
%%   comparison.  If the identifier is not recognised or not
 
827
%%   supported, all strings that are affected by it SHOULD be regarded
 
828
%%   as byte strings.
 
829
%%   
 
830
%%   Note that a character set specified MUST still prohibit the use
 
831
%%   of bytes 0x00 (Nul), 0x0A (LF) and 0x0d (CR). Character sets
 
832
%%   requiring the use of these characters MUST define a quoting
 
833
%%   mechanism that prevents these bytes appearing within text fields.
 
834
%%
 
835
%% a=sdplang:<language tag>
 
836
%%   This can be a session level attribute or a media level attribute.
 
837
%%   As a session level attribute, it specifies the language for the
 
838
%%   session description.  As a media level attribute, it specifies
 
839
%%   the language for any media-level SDP information field associated
 
840
%%   with that media.  Multiple sdplang attributes can be provided
 
841
%%   either at session or media level if multiple languages in the
 
842
%%   session description or media use multiple languages, in which
 
843
%%   case the order of the attributes indicates the order of
 
844
%%   importance of the various languages in the session or media from
 
845
%%   most important to least important.
 
846
%%   
 
847
%%   In general, sending session descriptions consisting of multiple
 
848
%%   languages should be discouraged.  Instead, multiple descriptions
 
849
%%   should be sent describing the session, one in each language.
 
850
%%   However this is not possible with all transport mechanisms, and
 
851
%%   so multiple sdplang attributes are allowed although not
 
852
%%   recommended.
 
853
%%   
 
854
%%   The sdplang attribute value must be a single RFC 1766 language
 
855
%%   tag in US-ASCII.  It is not dependent on the charset attribute.
 
856
%%   An sdplang attribute SHOULD be specified when a session is of
 
857
%%   sufficient scope to cross geographic boundaries where the
 
858
%%   language of recipients cannot be assumed, or where the session is
 
859
%%   in a different language from the locally assumed norm.
 
860
%% 
 
861
%% a=lang:<language tag>
 
862
%%   This can be a session level attribute or a media level attribute.
 
863
%%   As a session level attribute, it specifies the default language
 
864
%%   for the session being described.  As a media level attribute, it
 
865
%%   specifies the language for that media, overriding any session-
 
866
%%   level language specified.  Multiple lang attributes can be
 
867
%%   provided either at session or media level if multiple languages
 
868
%%   if the session description or media use multiple languages, in
 
869
%%   which case the order of the attributes indicates the order of
 
870
%%   importance of the various languages in the session or media from
 
871
%%   most important to least important.
 
872
%%
 
873
%%   The lang attribute value must be a single RFC 1766 language tag
 
874
%%   in US-ASCII. It is not dependent on the charset attribute.  A
 
875
%%   lang attribute SHOULD be specified when a session is of
 
876
%%   sufficient scope to cross geographic boundaries where the
 
877
%%   language of recipients cannot be assumed, or where the session is
 
878
%%   in a different language from the locally assumed norm.
 
879
%%
 
880
%% a=framerate:<frame rate>
 
881
%%   This gives the maximum video frame rate in frames/sec.  It is
 
882
%%   intended as a recommendation for the encoding of video data.
 
883
%%   Decimal representations of fractional values using the notation
 
884
%%   "<integer>.<fraction>" are allowed.  It is a media attribute, is
 
885
%%   only defined for video media, and is not dependent on charset.
 
886
%%
 
887
%% a=quality:<quality>
 
888
%%   This gives a suggestion for the quality of the encoding as an
 
889
%%   integer value.
 
890
%%   
 
891
%%   The intention of the quality attribute for video is to specify a
 
892
%%   non-default trade-off between frame-rate and still-image quality.
 
893
%%   For video, the value in the range 0 to 10, with the following
 
894
%%   suggested meaning:
 
895
%%   
 
896
%%   10 - the best still-image quality the compression scheme can
 
897
%%   give.
 
898
%%   
 
899
%%   5 - the default behaviour given no quality suggestion.
 
900
%%   
 
901
%%   0 - the worst still-image quality the codec designer thinks is
 
902
%%       still usable.
 
903
%%   
 
904
%%   It is a media attribute, and is not dependent on charset.
 
905
%% 
 
906
%% a=fmtp:<format> <format specific parameters>
 
907
%%   This attribute allows parameters that are specific to a
 
908
%%   particular format to be conveyed in a way that SDP doesn't have
 
909
%%   to understand them.  The format must be one of the formats
 
910
%%   specified for the media.  Format-specific parameters may be any
 
911
%%   set of parameters required to be conveyed by SDP and given
 
912
%%   unchanged to the media tool that will use this format.
 
913
%%
 
914
%%   It is a media attribute, and is not dependent on charset.
 
915
%% 
 
916
 
 
917
-record(megaco_sdp_a, {
 
918
          attribute,                            % string()
 
919
          value                                 % undefined | string()
 
920
         }
 
921
       ).
 
922
 
 
923
-record(megaco_sdp_a_rtpmap, {
137
924
          payload_type,                         % integer()
138
925
          encoding_name,                        % string()
139
926
          clock_rate,                           % integer()
140
927
          encoding_parms = []                   % [ string() ]
141
 
         }).
 
928
         }
 
929
       ).
142
930
                
143
 
-record(sdp_a_ptime, {
 
931
-record(megaco_sdp_a_ptime, {
144
932
          packet_time                           % integer()
 
933
         }
 
934
       ).
 
935
 
 
936
-record(megaco_sdp_a_quality, {
 
937
          quality                               % integer()
 
938
         }
 
939
       ).
 
940
 
 
941
-record(megaco_sdp_a_fmtp, {
 
942
          format,                               % string()
 
943
          param                                 % string()
 
944
         }
 
945
       ).
 
946
 
 
947
 
 
948
 
 
949
 
 
950
%% ===================================================================
 
951
%% 
 
952
%% Media Announcements
 
953
%% 
 
954
%% m=<media> <port> <transport> <fmt list>
 
955
%%
 
956
%% A session description may contain a number of media descriptions.
 
957
%% Each media description starts with an "m=" field, and is terminated
 
958
%% by either the next "m=" field or by the end of the session
 
959
%% description.  A media field also has several sub-fields:
 
960
%%
 
961
%% o The first sub-field is the media type.  Currently defined media are
 
962
%%   "audio", "video", "application", "data" and "control", though this
 
963
%%   list may be extended as new communication modalities emerge (e.g.,
 
964
%%   telepresense).  The difference between "application" and "data" is
 
965
%%   that the former is a media flow such as whiteboard information, and
 
966
%%   the latter is bulk-data transfer such as multicasting of program
 
967
%%   executables which will not typically be displayed to the user.
 
968
%%   "control" is used to specify an additional conference control
 
969
%%   channel for the session.
 
970
%%
 
971
%% o The second sub-field is the transport port to which the media
 
972
%%   stream will be sent.  The meaning of the transport port depends on
 
973
%%   the network being used as specified in the relevant "c" field and
 
974
%%   on the transport protocol defined in the third sub-field.  Other
 
975
%%   ports used by the media application (such as the RTCP port, see
 
976
%%   [2]) should be derived algorithmically from the base media port.
 
977
%%
 
978
%%   Note: For transports based on UDP, the value should be in the range
 
979
%%   1024 to 65535 inclusive.  For RTP compliance it should be an even
 
980
%%   number.
 
981
%%
 
982
%%   For applications where hierarchically encoded streams are being
 
983
%%   sent to a unicast address, it may be necessary to specify multiple
 
984
%%   transport ports.  This is done using a similar notation to that
 
985
%%   used for IP multicast addresses in the "c=" field:
 
986
%%
 
987
%%        m=<media> <port>/<number of ports> <transport> <fmt list>
 
988
%%
 
989
%%   In such a case, the ports used depend on the transport protocol.
 
990
%%   For RTP, only the even ports are used for data and the
 
991
%%   corresponding one-higher odd port is used for RTCP.  For example:
 
992
%%
 
993
%%                       m=video 49170/2 RTP/AVP 31
 
994
%%
 
995
%%   would specify that ports 49170 and 49171 form one RTP/RTCP pair and
 
996
%%   49172 and 49173 form the second RTP/RTCP pair.  RTP/AVP is the
 
997
%%   transport protocol and 31 is the format (see below).
 
998
%%
 
999
%%   It is illegal for both multiple addresses to be specified in the
 
1000
%%   "c=" field and for multiple ports to be specified in the "m=" field
 
1001
%%   in the same session description.
 
1002
%% 
 
1003
%% o The third sub-field is the transport protocol.  The transport
 
1004
%%   protocol values are dependent on the address-type field in the "c="
 
1005
%%   fields.  Thus a "c=" field of IP4 defines that the transport
 
1006
%%   protocol runs over IP4.  For IP4, it is normally expected that most
 
1007
%%   media traffic will be carried as RTP over UDP.  The following
 
1008
%%   transport protocols are preliminarily defined, but may be extended
 
1009
%%   through registration of new protocols with IANA:
 
1010
%%
 
1011
%%   - RTP/AVP - the IETF's Realtime Transport Protocol using the
 
1012
%%     Audio/Video profile carried over UDP.
 
1013
%%
 
1014
%%   - udp - User Datagram Protocol
 
1015
%%
 
1016
%%   If an application uses a single combined proprietary media format
 
1017
%%   and transport protocol over UDP, then simply specifying the
 
1018
%%   transport protocol as udp and using the format field to distinguish
 
1019
%%   the combined protocol is recommended.  If a transport protocol is
 
1020
%%   used over UDP to carry several distinct media types that need to be
 
1021
%%   distinguished by a session directory, then specifying the transport
 
1022
%%   protocol and media format separately is necessary. RTP is an
 
1023
%%   example of a transport-protocol that carries multiple payload
 
1024
%%   formats that must be distinguished by the session directory for it
 
1025
%%   to know how to start appropriate tools, relays, mixers or
 
1026
%%   recorders.
 
1027
%%
 
1028
%%   The main reason to specify the transport-protocol in addition to
 
1029
%%   the media format is that the same standard media formats may be
 
1030
%%   carried over different transport protocols even when the network
 
1031
%%   protocol is the same - a historical example is vat PCM audio and
 
1032
%%   RTP PCM audio.  In addition, relays and monitoring tools that are
 
1033
%%   transport-protocol-specific but format-independent are possible.
 
1034
%%
 
1035
%%   For RTP media streams operating under the RTP Audio/Video Profile
 
1036
%%   [3], the protocol field is "RTP/AVP".  Should other RTP profiles be
 
1037
%%   defined in the future, their profiles will be specified in the same
 
1038
%%   way.  For example, the protocol field "RTP/XYZ" would specify RTP
 
1039
%%   operating under a profile whose short name is "XYZ".
 
1040
%% 
 
1041
%% o The fourth and subsequent sub-fields are media formats.  For audio
 
1042
%%   and video, these will normally be a media payload type as defined
 
1043
%%   in the RTP Audio/Video Profile.
 
1044
%%
 
1045
%%   When a list of payload formats is given, this implies that all of
 
1046
%%   these formats may be used in the session, but the first of these
 
1047
%%   formats is the default format for the session.
 
1048
%%
 
1049
%%   For media whose transport protocol is not RTP or UDP the format
 
1050
%%   field is protocol specific.  Such formats should be defined in an
 
1051
%%   additional specification document.
 
1052
%%
 
1053
%%   For media whose transport protocol is RTP, SDP can be used to
 
1054
%%   provide a dynamic binding of media encoding to RTP payload type.
 
1055
%%   The encoding names in the RTP AV Profile do not specify unique
 
1056
%%   audio encodings (in terms of clock rate and number of audio
 
1057
%%   channels), and so they are not used directly in SDP format fields.
 
1058
%%   Instead, the payload type number should be used to specify the
 
1059
%%   format for static payload types and the payload type number along
 
1060
%%   with additional encoding information should be used for dynamically
 
1061
%%   allocated payload types.
 
1062
%%
 
1063
%%   An example of a static payload type is u-law PCM coded single
 
1064
%%   channel audio sampled at 8KHz.  This is completely defined in the
 
1065
%%   RTP Audio/Video profile as payload type 0, so the media field for
 
1066
%%   such a stream sent to UDP port 49232 is:
 
1067
%%
 
1068
%%                         m=video 49232 RTP/AVP 0
 
1069
%%
 
1070
%%   An example of a dynamic payload type is 16 bit linear encoded
 
1071
%%   stereo audio sampled at 16KHz.  If we wish to use dynamic RTP/AVP
 
1072
%%   payload type 98 for such a stream, additional information is
 
1073
%%   required to decode it:
 
1074
%%
 
1075
%%                        m=video 49232 RTP/AVP 98
 
1076
%%                        a=rtpmap:98 L16/16000/2
 
1077
%%
 
1078
%%   The general form of an rtpmap attribute is:
 
1079
%%
 
1080
%%   a=rtpmap:<payload type> <encoding name>/<clock rate>[/<encoding
 
1081
%%   parameters>]
 
1082
%%
 
1083
%%   For audio streams, <encoding parameters> may specify the number of
 
1084
%%   audio channels.  This parameter may be omitted if the number of
 
1085
%%   channels is one provided no additional parameters are needed.  For
 
1086
%%   video streams, no encoding parameters are currently specified.
 
1087
%%
 
1088
%%   Additional parameters may be defined in the future, but
 
1089
%%   codecspecific parameters should not be added.  Parameters added to
 
1090
%%   an rtpmap attribute should only be those required for a session
 
1091
%%   directory to make the choice of appropriate media too to
 
1092
%%   participate in a session.  Codec-specific parameters should be
 
1093
%%   added in other attributes.
 
1094
%%
 
1095
%%   Up to one rtpmap attribute can be defined for each media format
 
1096
%%   specified. Thus we might have:
 
1097
%%
 
1098
%%                     m=audio 49230 RTP/AVP 96 97 98
 
1099
%%                     a=rtpmap:96 L8/8000
 
1100
%%                     a=rtpmap:97 L16/8000
 
1101
%%                     a=rtpmap:98 L16/11025/2
 
1102
%% 
 
1103
%%   RTP profiles that specify the use of dynamic payload types must
 
1104
%%   define the set of valid encoding names and/or a means to register
 
1105
%%   encoding names if that profile is to be used with SDP.
 
1106
%%
 
1107
%%   Experimental encoding formats can also be specified using rtpmap.
 
1108
%%   RTP formats that are not registered as standard format names must
 
1109
%%   be preceded by "X-".  Thus a new experimental redundant audio
 
1110
%%   stream called GSMLPC using dynamic payload type 99 could be
 
1111
%%   specified as:
 
1112
%%
 
1113
%%                        m=video 49232 RTP/AVP 99
 
1114
%%                        a=rtpmap:99 X-GSMLPC/8000
 
1115
%%
 
1116
%%   Such an experimental encoding requires that any site wishing to
 
1117
%%   receive the media stream has relevant configured state in its
 
1118
%%   session directory to know which tools are appropriate.
 
1119
%%
 
1120
%%   Note that RTP audio formats typically do not include information
 
1121
%%   about the number of samples per packet.  If a non-default (as
 
1122
%%   defined in the RTP Audio/Video Profile) packetisation is required,
 
1123
%%   the "ptime" attribute is used as given below.
 
1124
%%
 
1125
%% o Formats for non-RTP media should be registered as MIME content
 
1126
%%   types as described in Appendix B.  For example, the LBL whiteboard
 
1127
%%   application might be registered as MIME content-type application/wb
 
1128
%%   with encoding considerations specifying that it operates over UDP,
 
1129
%%   with no appropriate file format.  In SDP this would then be
 
1130
%%   expressed using a combination of the "media" field and the "fmt"
 
1131
%%   field, as follows:
 
1132
%%
 
1133
%%                       m=application 32416 udp wb
 
1134
%% 
 
1135
 
 
1136
%% ma_media() -> audio | video | application | data | control
 
1137
-record(megaco_sdp_m, {
 
1138
          media,         % ma_media() | string()
 
1139
          port,          % integer()
 
1140
          num_ports,     % undefined | integer()
 
1141
          transport,     % string()
 
1142
          fmt_list = []  % [ string() ]
145
1143
         }).
146
1144
 
147
 
-record(sdp_s, {
148
 
          name                                  % string()
149
 
         }).
150
 
-record(sdp_i, {
151
 
          session_descriptor                    % string()
152
 
         }).
153
 
-record(sdp_u, {
154
 
          uri                                   % string()
155
 
         }).
156
 
-record(sdp_e, {
157
 
          email                                 % string()
158
 
         }).
159
 
-record(sdp_p, {
160
 
          phone_number                          % string()
161
 
         }).
162
 
 
163
1145
          
164
1146
-endif.