~ubuntu-branches/ubuntu/karmic/erlang/karmic-security

« back to all changes in this revision

Viewing changes to lib/asn1/doc/src/asn1_spec.xml

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
<?xml version="1.0" encoding="iso-8859-1" ?>
 
2
<!DOCTYPE chapter SYSTEM "chapter.dtd">
 
3
 
 
4
<chapter>
 
5
  <header>
 
6
    <copyright>
 
7
      <year>2003</year>
 
8
      <year>2007</year>
 
9
      <holder>Ericsson AB, All Rights Reserved</holder>
 
10
    </copyright>
 
11
    <legalnotice>
 
12
  The contents of this file are subject to the Erlang Public License,
 
13
  Version 1.1, (the "License"); you may not use this file except in
 
14
  compliance with the License. You should have received a copy of the
 
15
  Erlang Public License along with this software. If not, it can be
 
16
  retrieved online at http://www.erlang.org/.
 
17
 
 
18
  Software distributed under the License is distributed on an "AS IS"
 
19
  basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
20
  the License for the specific language governing rights and limitations
 
21
  under the License.
 
22
 
 
23
  The Initial Developer of the Original Code is Ericsson AB.
 
24
    </legalnotice>
 
25
 
 
26
    <title>Specialized Decodes</title>
 
27
    <prepared>EAB/UAB/UKH/KD Bertil Karlsson</prepared>
 
28
    <docno></docno>
 
29
    <date>2003-04-24</date>
 
30
    <rev>D</rev>
 
31
    <file>asn1_spec.sgml</file>
 
32
  </header>
 
33
  <marker id="SpecializedDecodes"></marker>
 
34
  <p>When performance is of highest priority and one is interested in
 
35
    a limited part of the ASN.1 encoded message, before one decide what
 
36
    to do with the rest of it, one may want to decode only this small
 
37
    part. The situation may be a server that has to decide to which
 
38
    addressee it will send a message. The addressee may be interested in
 
39
    the entire message, but the server may be a bottleneck that one want
 
40
    to spare any unnecessary load. Instead of making two <em>complete decodes</em> (the normal case of decode), one in the server and one
 
41
    in the addressee, it is only necessary to make one <em>specialized decode</em>(in the server) and another complete decode(in the
 
42
    addressee). The following specialized decodes <em>exclusive decode</em> and <em>selected decode</em> support to solve this and
 
43
    similar problems.
 
44
    </p>
 
45
  <p>So far this functionality is only provided when using the
 
46
    optimized BER_BIN version, that is when compiling with the
 
47
    options <c>ber_bin</c> and <c>optimize</c>. It does also work
 
48
    using the <c>driver</c> option. We have no intent to make this
 
49
    available on the default BER version, but maybe in the PER_BIN
 
50
    version (<c>per_bin</c>).
 
51
    </p>
 
52
 
 
53
  <section>
 
54
    <title>Exclusive Decode</title>
 
55
    <p>The basic idea with exclusive
 
56
      decode is that you specify which parts of the message you want to
 
57
      exclude from being decoded. These parts remain encoded and are
 
58
      returned in the value structure as binaries. They may be decoded
 
59
      in turn by passing them to a certain <c>decode_part/2</c>
 
60
      function. The performance gain is high when the message is large
 
61
      and you can do an exclusive decode and later on one or several
 
62
      decodes of the parts or a second complete decode instead of two or
 
63
      more complete decodes.
 
64
      </p>
 
65
 
 
66
    <section>
 
67
      <title>How To Make It Work</title>
 
68
      <p>In order to make exclusive decode work you have to do the
 
69
        following:
 
70
        </p>
 
71
      <list type="bulleted">
 
72
        <item>First,decide the name of the function for the exclusive
 
73
         decode.</item>
 
74
        <item>Second, write instructions that must consist of the name
 
75
         of the exclusive decode function, the name of the ASN.1
 
76
         specification and a notation that tells which parts of the
 
77
         message structure will be excluded from decode. These
 
78
         instructions shall be included in a configuration
 
79
         file. </item>
 
80
        <item>Third, compile with the additional option
 
81
        <c>asn1config</c>. The compiler searches for a configuration
 
82
         file with the same name as the ASN.1 spec but with the
 
83
         extension .asn1config. This configuration file is not the same
 
84
         as used for compilation of a set of files. See section
 
85
        <seealso marker="#UndecodedPart">Writing an Exclusive Decode Instruction.</seealso></item>
 
86
      </list>
 
87
    </section>
 
88
 
 
89
    <section>
 
90
      <title>User Interface</title>
 
91
      <p>The run-time user interface for exclusive decode consists of
 
92
        two different functions. First, the function for an exclusive
 
93
        decode, whose name the user decides in the configuration
 
94
        file. Second, the compiler generates a <c>decode_part/2</c>
 
95
        function when exclusive decode is chosen. This function decodes
 
96
        the parts that were left undecoded during the exclusive
 
97
        decode. Both functions are described below.
 
98
        </p>
 
99
      <p>If the exclusive decode function has for example got the name
 
100
        <c>decode_exclusive</c> and an ASN.1 encoded message
 
101
        <c>Bin</c> shall be exclusive decoded, the call is:</p>
 
102
      <pre>
 
103
{ok,Excl_Message} = 'MyModule':decode_exclusive(Bin)      </pre>
 
104
      <marker id="UndecodedPart"></marker>
 
105
      <p>The result <c>Excl_Message</c> has the same structure as an
 
106
        complete decode would have, except for the parts of the top-type
 
107
        that were not decoded. The undecoded parts will be on their place
 
108
        in the structure on the format <c>{Type_Key,Undecoded_Value}</c>.
 
109
        </p>
 
110
      <p>Each undecoded part that shall be decoded must be fed into the <c>decode_part/2</c> function,like:</p>
 
111
      <pre>
 
112
{ok,Part_Message} = 'MyModule':decode_part(Type_Key,Undecoded_Value)      </pre>
 
113
    </section>
 
114
 
 
115
    <section>
 
116
      <marker id="Exclusive Instruction"></marker>
 
117
      <title>Writing an Exclusive Decode Instruction</title>
 
118
      <p>This instruction is written in the configuration file on the
 
119
        format:</p>
 
120
      <pre>
 
121
 
 
122
Exclusive_Decode_Instruction = {exclusive_decode,{Module_Name,Decode_Instructions}}.
 
123
 
 
124
Module_Name = atom()
 
125
 
 
126
Decode_Instructions = [Decode_Instruction]+
 
127
 
 
128
Decode_Instruction = {Exclusive_Decode_Function_Name,Type_List}
 
129
 
 
130
Exclusive_Decode_Function_Name = atom()
 
131
 
 
132
Type_List = [Top_Type,Element_List]
 
133
 
 
134
Element_List = [Element]+
 
135
 
 
136
Element = {Name,parts} |
 
137
          {Name,undecoded} |
 
138
          {Name,Element_List}
 
139
 
 
140
Top_Type = atom()
 
141
 
 
142
Name = atom()
 
143
      </pre>
 
144
      <p>Observe that the instruction must be a valid Erlang term ended
 
145
        by a dot.
 
146
        </p>
 
147
      <p>In the <c>Type_List</c> the "path" from the top type to each
 
148
        undecoded sub-components is described. The top type of the path is
 
149
        an atom, the name of it. The action on each component/type that
 
150
        follows will be described by one of <c>{Name,parts}, {Name,undecoded}, {Name,Element_List}</c></p>
 
151
      <p>The use and effect of the actions are:
 
152
        </p>
 
153
      <list type="bulleted">
 
154
        <item><c>{Name,undecoded}</c> Tells that the element will be
 
155
         left undecoded during the exclusive decode. The type of Name may
 
156
         be any ASN.1 type. The value of element Name will be returned as a
 
157
         tuple,as mentioned <seealso marker="#UndecodedPart">above</seealso>, in the value structure of the top type.</item>
 
158
        <item><c>{Name,parts}</c> The type of Name may be one of
 
159
         SEQUENCE OF or SET OF. The action implies that the different
 
160
         components of Name will be left undecoded. The value of Name
 
161
         will be returned as a tuple, as <seealso marker="#UndecodedPart">above </seealso>, where the second element is a list of
 
162
         binaries. That is because the representation of a SEQUENCE OF/
 
163
         SET OF in Erlang is a list of its internal type. Any of the
 
164
         elements of this list or the entire list can be decoded by the
 
165
        <c>decode_part</c> function.</item>
 
166
        <item><c>{Name,Element_List}</c>This action is used when one or
 
167
         more of the sub-types of Name will be exclusive decoded.</item>
 
168
      </list>
 
169
      <p>Name in the actions above may be a component name of a
 
170
        SEQUENCE or a SET or a name of an alternative in a CHOICE.
 
171
        </p>
 
172
    </section>
 
173
 
 
174
    <section>
 
175
      <title>Example</title>
 
176
      <p>In the examples below we use the definitions from the following ASN.1 spec:</p>
 
177
      <marker id="Asn1spec"></marker>
 
178
      <codeinclude file="Seq.asn" tag="" type="none"></codeinclude>
 
179
      <p>If <c>Button</c> is a top type and we want to exclude
 
180
        component <c>number</c> from decode the Type_List in the
 
181
        instruction in the configuration file will be
 
182
        <c>['Button',[{number,undecoded}]]</c>. If we call the decode
 
183
        function <c>decode_Button_exclusive</c> the Decode_Instruction
 
184
        will be
 
185
        <c>{decode_Button_exclusive,['Button',[{number,undecoded}]]}</c>.
 
186
        </p>
 
187
      <p>We also have another top type <c>Window</c> whose sub
 
188
        component actions in type <c>Status</c> and the parts of component
 
189
        <c>buttonList</c> shall be left undecoded. For this type we name
 
190
        the function <c>decode__Window_exclusive</c>. The whole
 
191
        Exclusive_Decode_Instruction configuration is as follows: </p>
 
192
      <codeinclude file="Seq.asn1config" tag="" type="none"></codeinclude>
 
193
      <p></p>
 
194
      <image file="exclusive_Win_But">
 
195
        <icaption>Figure symbolizes the bytes of a Window:status message. The components buttonList and actions are excluded from decode. Only state and enabled are decoded when decode__Window_exclusive is called. </icaption>
 
196
      </image>
 
197
      <p></p>
 
198
      <p>Compiling GUI.asn including the configuration file is done like:</p>
 
199
      <pre>
 
200
unix> erlc -bber_bin +optimize +asn1config GUI.asn
 
201
 
 
202
erlang> asn1ct:compile('GUI',[ber_bin,optimize,asn1config]).      </pre>
 
203
      <p>The module can be used like:</p>
 
204
      <pre>
 
205
 
 
206
1> Button_Msg = {'Button',123,true}.
 
207
{'Button',123,true}
 
208
2> {ok,Button_Bytes} = 'GUI':encode('Button',Button_Msg).
 
209
{ok,[&lt;&lt;48&gt;&gt;,
 
210
     [6],
 
211
     [&lt;&lt;128&gt;&gt;,
 
212
      [1],
 
213
      123],
 
214
     [&lt;&lt;129&gt;&gt;,
 
215
      [1],
 
216
      255]]}
 
217
3> {ok,Exclusive_Msg_Button} = 'GUI':decode_Button_exclusive(list_to_binary(Button_Bytes)).
 
218
{ok,{'Button',{'Button_number',&lt;&lt;28,1,123&gt;&gt;},
 
219
         true}}
 
220
4> 'GUI':decode_part('Button_number',&lt;&lt;128,1,123&gt;&gt;).
 
221
{ok,123}
 
222
5> Window_Msg = 
 
223
{'Window',{status,{'Status',35,
 
224
              [{'Button',3,true},
 
225
               {'Button',4,false},
 
226
               {'Button',5,true},
 
227
               {'Button',6,true},
 
228
               {'Button',7,false},
 
229
               {'Button',8,true},
 
230
               {'Button',9,true},
 
231
               {'Button',10,false},
 
232
               {'Button',11,true},
 
233
               {'Button',12,true},
 
234
               {'Button',13,false},
 
235
               {'Button',14,true}],
 
236
              false,
 
237
              {possibleActions,[{'Action',16,{'Button',17,true}}]}}}}. 
 
238
{'Window',{status,{'Status',35,
 
239
              [{'Button',3,true},
 
240
               {'Button',4,false},
 
241
               {'Button',5,true},
 
242
               {'Button',6,true},
 
243
               {'Button',7,false},
 
244
               {'Button',8,true},
 
245
               {'Button',9,true},
 
246
               {'Button',10,false},
 
247
               {'Button',11,true},
 
248
               {'Button',12,true},
 
249
               {'Button',13,false},
 
250
               {'Button',14,true}],
 
251
              false,
 
252
              {possibleActions,[{'Action',16,{'Button',17,true}}]}}}}
 
253
6> {ok,Window_Bytes}='GUI':encode('Window',Window_Msg).
 
254
{ok,[&lt;&lt;161&gt;&gt;,
 
255
     [127],
 
256
     [&lt;&lt;128&gt;&gt;, ...
 
257
 
 
258
 
 
259
8> {ok,{status,{'Status',Int,{Type_Key_SeqOf,Val_SEQOF},
 
260
BoolOpt,{Type_Key_Choice,Val_Choice}}}}=
 
261
'GUI':decode_Window_status_exclusive(list_to_binary(Window_Bytes)).
 
262
{ok,{status,{'Status',35,
 
263
        {'Status_buttonList',[&lt;&lt;48,6,128,1,3,129,1,255&gt;&gt;,
 
264
                              &lt;&lt;48,6,128,1,4,129,1,0&gt;&gt;,
 
265
                              &lt;&lt;48,6,128,1,5,129,1,255&gt;&gt;,
 
266
                              &lt;&lt;48,6,128,1,6,129,1,255&gt;&gt;,
 
267
                              &lt;&lt;48,6,128,1,7,129,1,0&gt;&gt;,
 
268
                              &lt;&lt;48,6,128,1,8,129,1,255&gt;&gt;,
 
269
                              &lt;&lt;48,6,128,1,9,129,1,255&gt;&gt;,
 
270
                              &lt;&lt;48,6,128,1,10,129,1,0&gt;&gt;,
 
271
                              &lt;&lt;48,6,128,1,11,129,1,255&gt;&gt;,
 
272
                              &lt;&lt;48,6,128,1,12,129,1,255&gt;&gt;,
 
273
                              &lt;&lt;48,6,128,1,13,129,1,0&gt;&gt;,
 
274
                              &lt;&lt;48,6,128,1,14,129,1,255&gt;&gt;]},
 
275
        false,
 
276
        {'Status_actions',
 
277
&lt;&lt;163,21,160,19,48,17,2,1,16,160,12,172,10,171,8,48,6,128,1,...&gt;&gt;}}}}
 
278
10> 'GUI':decode_part(Type_Key_SeqOf,Val_SEQOF).
 
279
{ok,[{'Button',3,true},
 
280
     {'Button',4,false},
 
281
     {'Button',5,true},
 
282
     {'Button',6,true},
 
283
     {'Button',7,false},
 
284
     {'Button',8,true},
 
285
     {'Button',9,true},
 
286
     {'Button',10,false},
 
287
     {'Button',11,true},
 
288
     {'Button',12,true},
 
289
     {'Button',13,false},
 
290
     {'Button',14,true}]}
 
291
11> 'GUI':decode_part(Type_Key_SeqOf,hd(Val_SEQOF)).
 
292
{ok,{'Button',3,true}}
 
293
12> 'GUI':decode_part(Type_Key_Choice,Val_Choice).  
 
294
{ok,{possibleActions,[{'Action',16,{'Button',17,true}}]}}
 
295
      </pre>
 
296
    </section>
 
297
  </section>
 
298
 
 
299
  <section>
 
300
    <title>Selective Decode</title>
 
301
    <p>This specialized decode decodes one single subtype of a
 
302
      constructed value. It is the fastest method to extract one sub
 
303
      value. The typical use of this decode is when one want to
 
304
      inspect, for instance a version number,to be able to decide what
 
305
      to do with the entire value. The result is returned as
 
306
      <c>{ok,Value}</c> or <c>{error,Reason}</c>.
 
307
      </p>
 
308
 
 
309
    <section>
 
310
      <title>How To Make It Work</title>
 
311
      <p>The following steps are necessary:
 
312
        </p>
 
313
      <list type="bulleted">
 
314
        <item>Write instructions in the configuration
 
315
         file. Including the name of a user function, the name of the ASN.1
 
316
         specification and a notation that tells which part of the type
 
317
         will be decoded. </item>
 
318
        <item>Compile with the additional option
 
319
        <c>asn1config</c>. The compiler searches for a configuration file
 
320
         with the same name as the ASN.1 spec but with the extension
 
321
         .asn1config. In the same file you can provide configuration specs
 
322
         for exclusive decode as well. The generated Erlang module has the
 
323
         usual functionality for encode/decode preserved and the
 
324
         specialized decode functionality added. </item>
 
325
      </list>
 
326
    </section>
 
327
 
 
328
    <section>
 
329
      <title>User Interface</title>
 
330
      <p>The only new user interface function is the one provided by the
 
331
        user in the configuration file. You can invoke that function by
 
332
        the <c>ModuleName:FunctionName</c> notation.
 
333
        </p>
 
334
      <p>So, if you have the following spec
 
335
        <c>{selective_decode,{'ModuleName',[{selected_decode_Window,TypeList}]}}</c>
 
336
        in the con-fig file, you do the selective decode by
 
337
        <c>{ok,Result}='ModuleName':selected_decode_Window(EncodedBinary).</c></p>
 
338
    </section>
 
339
 
 
340
    <section>
 
341
      <marker id="Selective Instruction"></marker>
 
342
      <title>Writing a Selective Decode Instruction</title>
 
343
      <p>It is possible to describe one or many selective decode
 
344
        functions in a configuration file, you have to use the following
 
345
        notation:</p>
 
346
      <pre>
 
347
Selective_Decode_Instruction = {selective_decode,{Module_Name,Decode_Instructions}}.
 
348
 
 
349
Module_Name = atom()
 
350
 
 
351
Decode_Instructions = [Decode_Instruction]+
 
352
 
 
353
Decode_Instruction = {Selective_Decode_Function_Name,Type_List}
 
354
 
 
355
Selective_Decode_Function_Name = atom()
 
356
 
 
357
Type_List = [Top_Type|Element_List]
 
358
 
 
359
Element_List = Name|List_Selector
 
360
 
 
361
Name = atom()
 
362
 
 
363
List_Selector = [integer()]      </pre>
 
364
      <p>Observe that the instruction must be a valid Erlang term ended
 
365
        by a dot.
 
366
        </p>
 
367
      <p>The <c>Module_Name</c> is the same as the name of the ASN.1
 
368
        spec, but without the extension. A <c>Decode_Instruction</c> is
 
369
        a tuple with your chosen function name and the components from
 
370
        the top type that leads to the single type you want to
 
371
        decode. Notice that you have to choose a name of your function
 
372
        that will not be the same as any of the generated functions. The
 
373
        first element of the <c>Type_List</c> is the top type of the
 
374
        encoded message. In the <c>Element_List</c> it is followed by
 
375
        each of the component names that leads to selected type. Each of
 
376
        the names in the <c>Element_List</c> must be constructed types
 
377
        except the last name, which can be any type.
 
378
        </p>
 
379
      <p>The List_Selector makes it possible to choose one of the
 
380
        encoded components in a SEQUENCE OF/ SET OF. It is also possible
 
381
        to go further in that component and pick a sub type of that to
 
382
        decode. So in the <c>Type_List</c>: <c>['Window',status,buttonList,[1],number]</c> the
 
383
        component <c>buttonList</c> has to be a SEQUENCE OF or SET OF type. In
 
384
        this example component <c>number</c> of the first of the encoded
 
385
        elements in the SEQUENCE OF <c>buttonList</c> is selected. This apply on
 
386
        the ASN.1 spec <seealso marker="#Asn1spec">above</seealso>.
 
387
        </p>
 
388
    </section>
 
389
 
 
390
    <section>
 
391
      <title>Another Example</title>
 
392
      <p>In this example we use the same ASN.1 spec as <seealso marker="#Asn1spec">above</seealso>. A valid selective decode
 
393
        instruction is:</p>
 
394
      <pre>
 
395
{selective_decode,
 
396
    {'GUI',
 
397
        [{selected_decode_Window1,
 
398
            ['Window',status,buttonList, 
 
399
             [1],
 
400
             number]},
 
401
 {selected_decode_Action,
 
402
     ['Action',handle,number]},
 
403
 {selected_decode_Window2,
 
404
     ['Window',
 
405
      status,
 
406
      actions,
 
407
      possibleActions,
 
408
      [1],
 
409
      handle,number]}]}}.
 
410
      </pre>
 
411
      <p>The first <c>Decode_Instruction</c>,
 
412
        <c>{selected_decode_Window1,['Window',status,buttonList,[1],number]}</c>
 
413
        is commented in the previous section. The instruction
 
414
        <c>{selected_decode_Action,['Action',handle,number]}</c> picks
 
415
        the component <c>number</c> in the <c>handle</c> component of the type
 
416
        <c>Action</c>. If we have the value <c>ValAction = {'Action',17,{'Button',4711,false}}</c> the internal value 4711
 
417
        should be picked by <c>selected_decode_Action</c>. In an Erlang
 
418
        terminal it looks like:</p>
 
419
      <pre>
 
420
ValAction = {'Action',17,{'Button',4711,false}}.
 
421
{'Action',17,{'Button',4711,false}}
 
422
7> {ok,Bytes}='GUI':encode('Action',ValAction).
 
423
...
 
424
8> BinBytes = list_to_binary(Bytes).
 
425
&lt;&lt;48,18,2,1,17,160,13,172,11,171,9,48,7,128,2,18,103,129,1,0&gt;&gt;
 
426
9> 'GUI':selected_decode_Action(BinBytes).
 
427
{ok,4711}
 
428
10>       </pre>
 
429
      <p>The third instruction,
 
430
        <c>['Window',status,actions,possibleActions,[1],handle,number]</c>,
 
431
        which is a little more complicated,</p>
 
432
      <list type="bulleted">
 
433
        <item>starts with type <em>Window</em>. </item>
 
434
        <item>Picks component <em>status</em> of <c>Window</c> that is
 
435
         of type <c>Status</c>.</item>
 
436
        <item>Then takes component <em>actions</em> of type
 
437
        <c>Status</c>.</item>
 
438
        <item>Then <em>possibleActions</em> of the internal defined
 
439
         CHOICE type.</item>
 
440
        <item>Thereafter it goes into the first component of the
 
441
         SEQUENCE OF by <em>[1]</em>. That component is of type
 
442
        <c>Action</c>.</item>
 
443
        <item>The instruction next picks component
 
444
        <em>handle</em>.</item>
 
445
        <item>And finally component <em>number</em> of the type
 
446
        <c>Button</c>.</item>
 
447
      </list>
 
448
      <p>The following figures shows which components are in the
 
449
        TypeList
 
450
        <c>['Window',status,actions,possibleActions,[1],handle,number]</c>. And
 
451
        which part of a message that will be decoded by
 
452
        selected_decode_Window2.
 
453
        </p>
 
454
      <p></p>
 
455
      <image file="selective_TypeList">
 
456
        <icaption>The elements specified in the config file for selective decode of a sub-value in a Window message</icaption>
 
457
      </image>
 
458
      <p></p>
 
459
      <image file="selective_Window2">
 
460
        <icaption>Figure symbolizes the bytes of a Window:status message. Only the marked element is decoded when selected_decode_Window2 is called. </icaption>
 
461
      </image>
 
462
      <p>With the following example you can examine that both
 
463
        <c>selected_decode_Window2</c> and
 
464
        <c>selected_decode_Window1</c> decodes the intended sub-value
 
465
        of the value <c>Val</c></p>
 
466
      <pre>
 
467
1> Val = {'Window',{status,{'Status',12,
 
468
                    [{'Button',13,true},
 
469
                     {'Button',14,false},
 
470
                     {'Button',15,true},
 
471
                     {'Button',16,false}],
 
472
                    true,
 
473
                    {possibleActions,[{'Action',17,{'Button',18,false}},
 
474
                                      {'Action',19,{'Button',20,true}},
 
475
                                      {'Action',21,{'Button',22,false}}]}}}}
 
476
2> {ok,Bytes}='GUI':encode('Window',Val).
 
477
...
 
478
3> Bin = list_to_binary(Bytes).
 
479
&lt;&lt;161,101,128,1,12,161,32,48,6,128,1,13,129,1,255,48,6,128,1,14,129,1,0,48,6,128,1,15,129,...&gt;&gt;
 
480
4> 'GUI':selected_decode_Window1(Bin).
 
481
{ok,13}
 
482
5> 'GUI':selected_decode_Window2(Bin).
 
483
{ok,18}      </pre>
 
484
      <p>Observe that the value feed into the selective decode
 
485
        functions must be a binary.
 
486
        </p>
 
487
    </section>
 
488
  </section>
 
489
 
 
490
  <section>
 
491
    <title>Performance</title>
 
492
    <p>To give an indication on the possible performance gain using
 
493
      the specialized decodes, some measures have been performed. The
 
494
      relative figures in the outcome between selective, exclusive and
 
495
      complete decode (the normal case) depends on the structure of
 
496
      the type, the size of the message and on what level the
 
497
      selective and exclusive decodes are specified.
 
498
      </p>
 
499
 
 
500
    <section>
 
501
      <title>ASN.1 Specifications, Messages and Configuration</title>
 
502
      <p>The specs <seealso marker="#Asn1spec">GUI</seealso> and
 
503
        <url href="http://www.itu.int/ITU-T/asn1/database/itu-t/h/h248/2002/MEDIA-GATEWAY-CONTROL.html">MEDIA-GATEWAY-CONTROL</url>
 
504
        was used in the test.
 
505
        </p>
 
506
      <p>For the GUI spec the configuration looked like:</p>
 
507
      <pre>
 
508
{selective_decode,
 
509
  {'GUI',
 
510
    [{selected_decode_Window1,
 
511
         ['Window',
 
512
          status,buttonList,
 
513
          [1],
 
514
          number]},
 
515
     {selected_decode_Window2,
 
516
         ['Window',
 
517
          status,
 
518
          actions,
 
519
          possibleActions,
 
520
          [1],
 
521
          handle,number]}]}}.
 
522
     {exclusive_decode,
 
523
         {'GUI',
 
524
            [{decode_Window_status_exclusive,
 
525
                ['Window',
 
526
                 [{status,
 
527
                     [{buttonList,parts},
 
528
                      {actions,undecoded}]}]]}]}}.
 
529
      </pre>
 
530
      <p>The MEDIA-GATEWAY-CONTROL configuration was:</p>
 
531
      <pre>
 
532
{exclusive_decode,
 
533
  {'MEDIA-GATEWAY-CONTROL',
 
534
    [{decode_MegacoMessage_exclusive,
 
535
        ['MegacoMessage',
 
536
         [{authHeader,undecoded},
 
537
          {mess,
 
538
             [{mId,undecoded},
 
539
              {messageBody,undecoded}]}]]}]}}.
 
540
{selective_decode,
 
541
  {'MEDIA-GATEWAY-CONTROL',
 
542
    [{decode_MegacoMessage_selective,
 
543
         ['MegacoMessage',mess,version]}]}}.
 
544
      </pre>
 
545
      <p>The corresponding values were:</p>
 
546
      <pre>
 
547
{'Window',{status,{'Status',12,
 
548
              [{'Button',13,true},
 
549
               {'Button',14,false},
 
550
               {'Button',15,true},
 
551
               {'Button',16,false},
 
552
               {'Button',13,true},
 
553
               {'Button',14,false},
 
554
               {'Button',15,true},
 
555
               {'Button',16,false},
 
556
               {'Button',13,true},
 
557
               {'Button',14,false},
 
558
               {'Button',15,true},
 
559
               {'Button',16,false}],
 
560
              true,
 
561
              {possibleActions,
 
562
                 [{'Action',17,{'Button',18,false}},
 
563
                  {'Action',19,{'Button',20,true}},
 
564
                  {'Action',21,{'Button',22,false}},
 
565
                  {'Action',17,{'Button',18,false}},
 
566
                  {'Action',19,{'Button',20,true}},
 
567
                  {'Action',21,{'Button',22,false}},
 
568
                  {'Action',17,{'Button',18,false}},
 
569
                  {'Action',19,{'Button',20,true}},
 
570
                  {'Action',21,{'Button',22,false}},
 
571
                  {'Action',17,{'Button',18,false}},
 
572
                  {'Action',19,{'Button',20,true}},
 
573
                  {'Action',21,{'Button',22,false}},
 
574
                  {'Action',17,{'Button',18,false}},
 
575
                  {'Action',19,{'Button',20,true}},
 
576
                  {'Action',21,{'Button',22,false}},
 
577
                  {'Action',17,{'Button',18,false}},
 
578
                  {'Action',19,{'Button',20,true}},
 
579
                  {'Action',21,{'Button',22,false}}]}}}}
 
580
 
 
581
 
 
582
{'MegacoMessage',asn1_NOVALUE,
 
583
  {'Message',1,
 
584
    {ip4Address,
 
585
      {'IP4Address',[125,125,125,111],55555}},
 
586
  {transactions,
 
587
    [{transactionReply,
 
588
      {'TransactionReply',50007,asn1_NOVALUE,
 
589
       {actionReplies,
 
590
        [{'ActionReply',0,asn1_NOVALUE,asn1_NOVALUE,
 
591
          [{auditValueReply,{auditResult,{'AuditResult',
 
592
            {'TerminationID',[],[255,255,255]},
 
593
             [{mediaDescriptor,
 
594
               {'MediaDescriptor',asn1_NOVALUE,
 
595
                {multiStream,
 
596
                 [{'StreamDescriptor',1,
 
597
                   {'StreamParms',
 
598
                    {'LocalControlDescriptor',
 
599
                     sendRecv,
 
600
                     asn1_NOVALUE,
 
601
                     asn1_NOVALUE,
 
602
                     [{'PropertyParm',
 
603
                       [0,11,0,7],
 
604
                       [[52,48]],
 
605
                       asn1_NOVALUE}]},
 
606
                    {'LocalRemoteDescriptor',
 
607
                     [[{'PropertyParm',
 
608
                        [0,0,176,1],
 
609
                        [[48]],
 
610
                        asn1_NOVALUE},
 
611
                       {'PropertyParm',
 
612
                         [0,0,176,8],
 
613
                         [[73,78,32,73,80,52,32,49,50,53,46,49,
 
614
                           50,53,46,49,50,53,46,49,49,49]],
 
615
                         asn1_NOVALUE},
 
616
                       {'PropertyParm',
 
617
                         [0,0,176,15],
 
618
                         [[97,117,100,105,111,32,49,49,49,49,32,
 
619
                           82,84,80,47,65,86,80,32,32,52]],
 
620
                         asn1_NOVALUE},
 
621
                       {'PropertyParm',
 
622
                         [0,0,176,12],
 
623
                         [[112,116,105,109,101,58,51,48]],
 
624
                         asn1_NOVALUE}]]},
 
625
                    {'LocalRemoteDescriptor',
 
626
                     [[{'PropertyParm',
 
627
                         [0,0,176,1],
 
628
                         [[48]],
 
629
                         asn1_NOVALUE},
 
630
                       {'PropertyParm',
 
631
                         [0,0,176,8],
 
632
                         [[73,78,32,73,80,52,32,49,50,52,46,49,50,
 
633
                           52,46,49,50,52,46,50,50,50]],
 
634
                         asn1_NOVALUE},
 
635
                       {'PropertyParm',
 
636
                         [0,0,176,15],
 
637
                         [[97,117,100,105,111,32,50,50,50,50,32,82,
 
638
                           84,80,47,65,86,80,32,32,52]],
 
639
                         asn1_NOVALUE},
 
640
                       {'PropertyParm',
 
641
                         [0,0,176,12],
 
642
                         [[112,116,105,109,101,58,51,48]],
 
643
                         asn1_NOVALUE}]]}}}]}}},
 
644
              {packagesDescriptor,
 
645
               [{'PackagesItem',[0,11],1},
 
646
                {'PackagesItem',[0,11],1}]},
 
647
              {statisticsDescriptor,
 
648
               [{'StatisticsParameter',[0,12,0,4],[[49,50,48,48]]},
 
649
                {'StatisticsParameter',[0,11,0,2],[[54,50,51,48,48]]},
 
650
                {'StatisticsParameter',[0,12,0,5],[[55,48,48]]},
 
651
                {'StatisticsParameter',[0,11,0,3],[[52,53,49,48,48]]},
 
652
                {'StatisticsParameter',[0,12,0,6],[[48,46,50]]},
 
653
                {'StatisticsParameter',[0,12,0,7],[[50,48]]},
 
654
                {'StatisticsParameter',[0,12,0,8],[[52,48]]}]}]}}}]}]}}}]}}}      
 
655
      </pre>
 
656
      <p>The size of the encoded values was 458 bytes for GUI and 464
 
657
        bytes for MEDIA-GATEWAY-CONTROL.
 
658
        </p>
 
659
    </section>
 
660
 
 
661
    <section>
 
662
      <title>Results</title>
 
663
      <p>The ASN.1 specs in the test are compiled with the options
 
664
        <c>ber_bin, optimize, driver</c> and <c>asn1config</c>. If the
 
665
        <c>driver</c> option had been omitted there should have been
 
666
        higher values for <c>decode</c> and <c>decode_part</c>.
 
667
        </p>
 
668
      <p>The test program runs 10000 decodes on the value, resulting
 
669
        in a printout with the elapsed time in microseconds for the
 
670
        total number of decodes.
 
671
        </p>
 
672
      <table>
 
673
        <row>
 
674
          <cell align="left" valign="top"><em>Function</em></cell>
 
675
          <cell align="left" valign="top"><em>Time</em>(microseconds)</cell>
 
676
          <cell align="left" valign="top"><em>Kind of Decode</em></cell>
 
677
          <cell align="left" valign="top"><em>ASN.1 spec</em></cell>
 
678
          <cell align="left" valign="top"><em>% of time vs. complete decode</em></cell>
 
679
        </row>
 
680
        <row>
 
681
          <cell align="left" valign="middle"><c>decode_MegacoMessage_selective/1</c></cell>
 
682
          <cell align="left" valign="middle"><c>374045</c></cell>
 
683
          <cell align="left" valign="middle"><c>selective</c></cell>
 
684
          <cell align="left" valign="middle"><c>MEDIA-GATEWAY-CONTROL</c></cell>
 
685
          <cell align="left" valign="middle"><em>8.3</em></cell>
 
686
        </row>
 
687
        <row>
 
688
          <cell align="left" valign="middle"><c>decode_MegacoMessage_exclusive/1</c></cell>
 
689
          <cell align="left" valign="middle"><c>621107</c></cell>
 
690
          <cell align="left" valign="middle"><c>exclusive</c></cell>
 
691
          <cell align="left" valign="middle"><c>MEDIA-GATEWAY-CONTROL</c></cell>
 
692
          <cell align="left" valign="middle"><em>13.8</em></cell>
 
693
        </row>
 
694
        <row>
 
695
          <cell align="left" valign="middle"><c>decode/2</c></cell>
 
696
          <cell align="left" valign="middle"><c>4507457</c></cell>
 
697
          <cell align="left" valign="middle"><c>complete</c></cell>
 
698
          <cell align="left" valign="middle"><c>MEDIA-GATEWAY-CONTROL</c></cell>
 
699
          <cell align="left" valign="middle"><em>100</em></cell>
 
700
        </row>
 
701
        <row>
 
702
          <cell align="left" valign="middle"><c>selected_decode_Window1/1</c></cell>
 
703
          <cell align="left" valign="middle"><c>449585</c></cell>
 
704
          <cell align="left" valign="middle"><c>selective</c></cell>
 
705
          <cell align="left" valign="middle"><c>GUI</c></cell>
 
706
          <cell align="left" valign="middle"><em>7.6</em></cell>
 
707
        </row>
 
708
        <row>
 
709
          <cell align="left" valign="middle"><c>selected_decode_Window2/1</c></cell>
 
710
          <cell align="left" valign="middle"><c>890666</c></cell>
 
711
          <cell align="left" valign="middle"><c>selective</c></cell>
 
712
          <cell align="left" valign="middle"><c>GUI</c></cell>
 
713
          <cell align="left" valign="middle"><em>15.1</em></cell>
 
714
        </row>
 
715
        <row>
 
716
          <cell align="left" valign="middle"><c>decode_Window_status_exclusive/1</c></cell>
 
717
          <cell align="left" valign="middle"><c>1251878</c></cell>
 
718
          <cell align="left" valign="middle"><c>exclusive</c></cell>
 
719
          <cell align="left" valign="middle"><c>GUI</c></cell>
 
720
          <cell align="left" valign="middle"><em>21.3</em></cell>
 
721
        </row>
 
722
        <row>
 
723
          <cell align="left" valign="middle"><c>decode/2</c></cell>
 
724
          <cell align="left" valign="middle"><c>5889197</c></cell>
 
725
          <cell align="left" valign="middle"><c>complete</c></cell>
 
726
          <cell align="left" valign="middle"><c>GUI</c></cell>
 
727
          <cell align="left" valign="middle"><em>100</em></cell>
 
728
        </row>
 
729
        <tcaption>Results of complete, exclusive and selective decode</tcaption>
 
730
      </table>
 
731
      <p>Another interesting question is what the relation is between
 
732
        a complete decode, an exclusive decode followed by
 
733
        <c>decode_part</c> of the excluded parts and a selective decode
 
734
        followed by a complete decode. Some situations may be compared to
 
735
        this simulation, e.g. inspect a sub-value and later on look at
 
736
        the entire value. The following table shows figures from this
 
737
        test. The number of loops and time unit is the same as in the
 
738
        previous test.
 
739
        </p>
 
740
      <table>
 
741
        <row>
 
742
          <cell align="left" valign="top"><em>Actions</em></cell>
 
743
          <cell align="left" valign="top"><em>Function</em>&nbsp;&nbsp;&nbsp;&nbsp;</cell>
 
744
          <cell align="left" valign="top"><em>Time</em>(microseconds)</cell>
 
745
          <cell align="left" valign="top"><em>ASN.1 spec</em></cell>
 
746
          <cell align="left" valign="top"><em>% of time vs. complete decode</em></cell>
 
747
        </row>
 
748
        <row>
 
749
          <cell align="left" valign="middle"><c>complete</c></cell>
 
750
          <cell align="left" valign="middle"><c>decode/2</c></cell>
 
751
          <cell align="left" valign="middle"><c>4507457</c></cell>
 
752
          <cell align="left" valign="middle"><c>MEDIA-GATEWAY-CONTROL</c></cell>
 
753
          <cell align="left" valign="middle"><em>100</em></cell>
 
754
        </row>
 
755
        <row>
 
756
          <cell align="left" valign="middle"><c>selective and complete</c></cell>
 
757
          <cell align="left" valign="middle"><c>decode_&shy;MegacoMessage_&shy;selective/1</c></cell>
 
758
          <cell align="left" valign="middle"><c>4881502</c></cell>
 
759
          <cell align="left" valign="middle"><c>MEDIA-GATEWAY-CONTROL</c></cell>
 
760
          <cell align="left" valign="middle"><em>108.3</em></cell>
 
761
        </row>
 
762
        <row>
 
763
          <cell align="left" valign="middle"><c>exclusive and decode_part</c></cell>
 
764
          <cell align="left" valign="middle"><c>decode_&shy;MegacoMessage_&shy;exclusive/1</c></cell>
 
765
          <cell align="left" valign="middle"><c>5481034</c></cell>
 
766
          <cell align="left" valign="middle"><c>MEDIA-GATEWAY-CONTROL</c></cell>
 
767
          <cell align="left" valign="middle"><em>112.3</em></cell>
 
768
        </row>
 
769
        <row>
 
770
          <cell align="left" valign="middle"><c>complete</c></cell>
 
771
          <cell align="left" valign="middle"><c>decode/2</c></cell>
 
772
          <cell align="left" valign="middle"><c>5889197</c></cell>
 
773
          <cell align="left" valign="middle"><c>GUI</c></cell>
 
774
          <cell align="left" valign="middle"><em>100</em></cell>
 
775
        </row>
 
776
        <row>
 
777
          <cell align="left" valign="middle"><c>selective and complete</c></cell>
 
778
          <cell align="left" valign="middle"><c>selected_&shy;decode_&shy;Window1/1</c></cell>
 
779
          <cell align="left" valign="middle"><c>6337636</c></cell>
 
780
          <cell align="left" valign="middle"><c>GUI</c></cell>
 
781
          <cell align="left" valign="middle"><em>107.6</em></cell>
 
782
        </row>
 
783
        <row>
 
784
          <cell align="left" valign="middle"><c>selective and complete</c></cell>
 
785
          <cell align="left" valign="middle"><c>selected_&shy;decode_&shy;Window2/1</c></cell>
 
786
          <cell align="left" valign="middle"><c>6795319</c></cell>
 
787
          <cell align="left" valign="middle"><c>GUI</c></cell>
 
788
          <cell align="left" valign="middle"><em>115.4</em></cell>
 
789
        </row>
 
790
        <row>
 
791
          <cell align="left" valign="middle"><c>exclusive and decode_part</c></cell>
 
792
          <cell align="left" valign="middle"><c>decode_&shy;Window_&shy;status_&shy;exclusive/1</c></cell>
 
793
          <cell align="left" valign="middle"><c>6249200</c></cell>
 
794
          <cell align="left" valign="middle"><c>GUI</c></cell>
 
795
          <cell align="left" valign="middle"><em>106.1</em></cell>
 
796
        </row>
 
797
        <tcaption>Results of complete, exclusive + decode_part and selective + complete decodes</tcaption>
 
798
      </table>
 
799
      <p>Other ASN.1 types and values can differ much from these
 
800
        figures. Therefore it is important that you, in every case where
 
801
        you intend to use either of these decodes, perform some tests
 
802
        that shows if you will benefit your purpose.
 
803
        </p>
 
804
    </section>
 
805
 
 
806
    <section>
 
807
      <title>Comments</title>
 
808
      <p>Generally speaking the gain of selective and exclusive decode
 
809
        in advance of complete decode is greater the bigger value and the
 
810
        less deep in the structure you have to decode. One should also
 
811
        prefer selective decode instead of exclusive decode if you are
 
812
        interested in just one single sub-value.</p>
 
813
      <p>Another observation is that the exclusive decode followed by
 
814
        decode_part decodes is very attractive if the parts will be sent
 
815
        to different servers for decoding or if one in some cases not is
 
816
        interested in all parts.</p>
 
817
      <p>The fastest selective decode are when the decoded type is a
 
818
        primitive type and not so deep in the structure of the top
 
819
        type. The <c>selected_decode_Window2</c> decodes a big constructed
 
820
        value, which explains why this operation is relatively slow.</p>
 
821
      <p>It may vary from case to case which combination of
 
822
        selective/complete decode or exclusive/part decode is the fastest.</p>
 
823
    </section>
 
824
  </section>
 
825
</chapter>
 
826