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

« back to all changes in this revision

Viewing changes to lib/orber/test/cdrlib_SUITE.erl

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

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1997-2011. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
%%
 
19
%%
 
20
%%-----------------------------------------------------------------
 
21
%% 
 
22
%% Description:
 
23
%% Test suite for the CDR basic type encode/decode functions
 
24
%%
 
25
%%-----------------------------------------------------------------
 
26
-module(cdrlib_SUITE).
 
27
 
 
28
-include_lib("test_server/include/test_server.hrl").
 
29
 
 
30
-define(default_timeout, ?t:minutes(3)).
 
31
 
 
32
%%-----------------------------------------------------------------
 
33
%% External exports
 
34
%%-----------------------------------------------------------------
 
35
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
36
         init_per_group/2,end_per_group/2]).
 
37
 
 
38
%%-----------------------------------------------------------------
 
39
%% Internal exports
 
40
%%-----------------------------------------------------------------
 
41
-compile(export_all).
 
42
 
 
43
%%-----------------------------------------------------------------
 
44
%% Func: all/1
 
45
%% Args: 
 
46
%% Returns: 
 
47
%%-----------------------------------------------------------------
 
48
suite() -> [{ct_hooks,[ts_install_cth]}].
 
49
 
 
50
all() -> 
 
51
    [short, ushort, long, ulong, longlong, ulonglong,
 
52
     boolean, character, octet, float, double, enum].
 
53
 
 
54
groups() -> 
 
55
    [].
 
56
 
 
57
init_per_suite(Config) ->
 
58
    Config.
 
59
 
 
60
end_per_suite(_Config) ->
 
61
    ok.
 
62
 
 
63
init_per_group(_GroupName, Config) ->
 
64
    Config.
 
65
 
 
66
end_per_group(_GroupName, Config) ->
 
67
    Config.
 
68
 
 
69
 
 
70
%%-----------------------------------------------------------------
 
71
%% Init and cleanup functions.
 
72
%%-----------------------------------------------------------------
 
73
 
 
74
init_per_testcase(_Case, Config) ->
 
75
    ?line Dog=test_server:timetrap(?default_timeout),
 
76
    [{watchdog, Dog}|Config].
 
77
 
 
78
 
 
79
end_per_testcase(_Case, Config) ->
 
80
    Dog = ?config(watchdog, Config),
 
81
    test_server:timetrap_cancel(Dog),
 
82
    ok.
 
83
 
 
84
%%-----------------------------------------------------------------
 
85
%% Test Case: short integer test
 
86
%% Description: 
 
87
%%-----------------------------------------------------------------
 
88
short(doc) -> ["Description", "more description"];
 
89
short(suite) -> [];
 
90
short(_) ->
 
91
    short_big_loop([-32768, -4040, -1, 0, 4040, 32767]),
 
92
    short_little_loop([-32768, -4040, -1, 0, 4040, 32767]),
 
93
    bad_short().
 
94
 
 
95
short_big_loop([]) ->
 
96
    ok;
 
97
short_big_loop([X |List]) ->
 
98
    ?line [CodedType] = cdrlib:enc_short(X, []),
 
99
    ?line {X, <<>>} = cdrlib:dec_short(big, CodedType),
 
100
    short_big_loop(List),
 
101
    ok.
 
102
 
 
103
short_little_loop([]) ->
 
104
    ok;
 
105
short_little_loop([X |List]) ->
 
106
    ?line CodedType = enc_short_little(X, []),
 
107
    ?line {X, <<>>} = cdrlib:dec_short(little, CodedType),
 
108
    short_little_loop(List),
 
109
    ok.
 
110
 
 
111
enc_short_little(X, Message) -> 
 
112
    list_to_binary([(X) band 16#ff, ((X) bsr 8) band 16#ff | Message]).
 
113
 
 
114
bad_short() ->
 
115
    ?line {'EXCEPTION', _} = (catch cdrlib:enc_short('atom', [])),
 
116
    ?line [CodedType] = cdrlib:enc_char($a, []),
 
117
    ?line {'EXIT', _} = (catch cdrlib:dec_short(big, CodedType)),
 
118
    ok.
 
119
%%-----------------------------------------------------------------
 
120
%% Test Case: unsigned short integer test
 
121
%% Description: 
 
122
%%-----------------------------------------------------------------
 
123
ushort(doc) -> ["Description", "more description"];
 
124
ushort(suite) -> [];
 
125
ushort(_) ->
 
126
    ushort_big_loop([0, 4040, 65535]),
 
127
    ushort_little_loop([0, 4040, 65535]),
 
128
    bad_ushort().
 
129
 
 
130
ushort_big_loop([]) ->
 
131
    ok;
 
132
ushort_big_loop([X |List]) ->
 
133
    ?line [CodedType] = cdrlib:enc_unsigned_short(X, []),
 
134
    ?line {X, <<>>} = cdrlib:dec_unsigned_short(big, CodedType),
 
135
    ushort_big_loop(List),
 
136
    ok.
 
137
 
 
138
ushort_little_loop([]) ->
 
139
    ok;
 
140
ushort_little_loop([X |List]) ->
 
141
    ?line CodedType = enc_ushort_little(X, []),
 
142
    ?line {X, <<>>} = cdrlib:dec_unsigned_short(little, CodedType),
 
143
    ushort_little_loop(List),
 
144
    ok.
 
145
 
 
146
enc_ushort_little(X, Message) -> 
 
147
    list_to_binary([(X) band 16#ff, ((X) bsr 8) band 16#ff | Message]).
 
148
 
 
149
bad_ushort() ->
 
150
    ok.
 
151
%%-----------------------------------------------------------------
 
152
%% Test Case: long integer test
 
153
%% Description: 
 
154
%%-----------------------------------------------------------------
 
155
long(doc) -> ["Description", "more description"];
 
156
long(suite) -> [];
 
157
long(_) ->
 
158
    long_big_loop([-2147483648, -40404040, -32768, -4040, -1,
 
159
                   0, 4040, 32767, 40404040, 2147483647]),
 
160
    long_little_loop([-2147483648, -40404040, -32768, -4040, -1,
 
161
                      0, 4040, 32767, 40404040, 2147483647]),
 
162
    bad_long().
 
163
    
 
164
 
 
165
long_big_loop([]) ->
 
166
    ok;
 
167
long_big_loop([X |List]) ->
 
168
    ?line [CodedType] = cdrlib:enc_long(X, []),
 
169
    ?line {X, <<>>} = cdrlib:dec_long(big, CodedType),
 
170
    long_big_loop(List),
 
171
    ok.
 
172
 
 
173
long_little_loop([]) ->
 
174
    ok;
 
175
long_little_loop([X |List]) ->
 
176
    ?line CodedType = enc_long_little(X, []),
 
177
    ?line {X, <<>>} = cdrlib:dec_long(little, CodedType),
 
178
    long_little_loop(List),
 
179
    ok.
 
180
 
 
181
enc_long_little(X, Message) -> 
 
182
    list_to_binary([(X) band 16#ff, ((X) bsr 8) band 16#ff, ((X) bsr 16) band 16#ff,
 
183
                    ((X) bsr 24) band 16#ff | Message]).
 
184
 
 
185
bad_long() ->
 
186
    ok.
 
187
 
 
188
%%-----------------------------------------------------------------
 
189
%% Test Case: unsigned long integer test
 
190
%% Description: 
 
191
%%-----------------------------------------------------------------
 
192
ulong(doc) -> ["Description", "more description"];
 
193
ulong(suite) -> [];
 
194
ulong(_) -> 
 
195
    ulong_big_loop([0, 4040, 65535, 40404040, 2147483647, 4294967295]),
 
196
    ulong_little_loop([0, 4040, 65535, 40404040, 2147483647, 4294967295]),
 
197
    bad_ulong().
 
198
    
 
199
 
 
200
ulong_big_loop([]) ->
 
201
    ok;
 
202
ulong_big_loop([X |List]) ->
 
203
    ?line [CodedType] = cdrlib:enc_unsigned_long(X, []),
 
204
    ?line {X, <<>>} = cdrlib:dec_unsigned_long(big, CodedType),
 
205
    ulong_big_loop(List),
 
206
    ok.
 
207
 
 
208
ulong_little_loop([]) ->
 
209
    ok;
 
210
ulong_little_loop([X |List]) ->
 
211
    ?line CodedType = enc_ulong_little(X, []),
 
212
    ?line {X, <<>>} = cdrlib:dec_unsigned_long(little, CodedType),
 
213
    ulong_little_loop(List),
 
214
    ok.
 
215
 
 
216
enc_ulong_little(X, Message) -> 
 
217
    list_to_binary([(X) band 16#ff, ((X) bsr 8) band 16#ff, ((X) bsr 16) band 16#ff,
 
218
                    ((X) bsr 24) band 16#ff | Message]).
 
219
 
 
220
 
 
221
bad_ulong() ->
 
222
    ok.
 
223
 
 
224
%%-----------------------------------------------------------------
 
225
%% Test Case: long integer test
 
226
%% Description: 
 
227
%%-----------------------------------------------------------------
 
228
longlong(doc) -> ["Description", "more description"];
 
229
longlong(suite) -> [];
 
230
longlong(_) ->
 
231
    longlong_big_loop([-2147483648, -40404040, -32768, -4040, -1,
 
232
                   0, 4040, 32767, 40404040, 2147483647]),
 
233
    longlong_little_loop([-2147483648, -40404040, -32768, -4040, -1,
 
234
                      0, 4040, 32767, 40404040, 2147483647]),
 
235
    bad_longlong().
 
236
    
 
237
 
 
238
longlong_big_loop([]) ->
 
239
    ok;
 
240
longlong_big_loop([X |List]) ->
 
241
    ?line [CodedType] = cdrlib:enc_longlong(X, []),
 
242
    ?line {X, <<>>} = cdrlib:dec_longlong(big, CodedType),
 
243
    longlong_big_loop(List),
 
244
    ok.
 
245
 
 
246
longlong_little_loop([]) ->
 
247
    ok;
 
248
longlong_little_loop([X |List]) ->
 
249
    ?line CodedType = enc_longlong_little(X, []),
 
250
    ?line {X, <<>>} = cdrlib:dec_longlong(little, CodedType),
 
251
    longlong_little_loop(List),
 
252
    ok.
 
253
 
 
254
enc_longlong_little(X, Message) -> 
 
255
    list_to_binary([(X) band 16#ff, ((X) bsr 8) band 16#ff, ((X) bsr 16) band 16#ff,
 
256
                    ((X) bsr 24) band 16#ff, ((X) bsr 32) band 16#ff, ((X) bsr 40) band 16#ff,
 
257
                    ((X) bsr 48) band 16#ff, ((X) bsr 56) band 16#ff | Message]).
 
258
 
 
259
bad_longlong() ->
 
260
    ok.
 
261
 
 
262
%%-----------------------------------------------------------------
 
263
%% Test Case: unsigned long integer test
 
264
%% Description: 
 
265
%%-----------------------------------------------------------------
 
266
ulonglong(doc) -> ["Description", "more description"];
 
267
ulonglong(suite) -> [];
 
268
ulonglong(_) -> 
 
269
    ulonglong_big_loop([0, 4040, 65535, 40404040, 2147483647, 4294967295]),
 
270
    ulonglong_little_loop([0, 4040, 65535, 40404040, 2147483647, 4294967295]),
 
271
    bad_ulonglong().
 
272
    
 
273
 
 
274
ulonglong_big_loop([]) ->
 
275
    ok;
 
276
ulonglong_big_loop([X |List]) ->
 
277
    ?line [CodedType] = cdrlib:enc_unsigned_longlong(X, []),
 
278
    ?line {X, <<>>} = cdrlib:dec_unsigned_longlong(big, CodedType),
 
279
    ulonglong_big_loop(List),
 
280
    ok.
 
281
 
 
282
ulonglong_little_loop([]) ->
 
283
    ok;
 
284
ulonglong_little_loop([X |List]) ->
 
285
    ?line CodedType = enc_ulonglong_little(X, []),
 
286
    ?line {X, <<>>} = cdrlib:dec_unsigned_longlong(little, CodedType),
 
287
    ulonglong_little_loop(List),
 
288
    ok.
 
289
 
 
290
enc_ulonglong_little(X, Message) -> 
 
291
    list_to_binary([(X) band 16#ff, ((X) bsr 8) band 16#ff, ((X) bsr 16) band 16#ff,
 
292
                    ((X) bsr 24) band 16#ff, ((X) bsr 32) band 16#ff, ((X) bsr 40) band 16#ff,
 
293
                    ((X) bsr 48) band 16#ff, ((X) bsr 56) band 16#ff | Message]).
 
294
 
 
295
bad_ulonglong() ->
 
296
    ok.
 
297
 
 
298
 
 
299
 
 
300
%%-----------------------------------------------------------------
 
301
%% Test Case: boolean test
 
302
%% Description: 
 
303
%%-----------------------------------------------------------------
 
304
boolean(doc) -> ["Description", "more description"];
 
305
boolean(suite) -> [];
 
306
boolean(_) ->
 
307
    ?line [CodedTrue] = cdrlib:enc_bool('true', []),
 
308
    ?line {'true', <<>>} = cdrlib:dec_bool(CodedTrue),
 
309
    ?line [CodedFalse] = cdrlib:enc_bool('false', []),
 
310
    ?line {'false', <<>>} = cdrlib:dec_bool(CodedFalse),
 
311
    ok.
 
312
 
 
313
%%-----------------------------------------------------------------
 
314
%% Test Case: character test
 
315
%% Description: 
 
316
%%-----------------------------------------------------------------
 
317
character(doc) -> ["Description", "more description"];
 
318
character(suite) -> [];
 
319
character(_) ->
 
320
    ?line [Coded_0] = cdrlib:enc_char($0, []),
 
321
    ?line {$0, <<>>} = cdrlib:dec_char(Coded_0),
 
322
    ?line [Coded_a] = cdrlib:enc_char($a, []),
 
323
    ?line {$a, <<>>} = cdrlib:dec_char(Coded_a),
 
324
    ?line [Coded_Z] = cdrlib:enc_char($Z, []),
 
325
    ?line {$Z, <<>>} = cdrlib:dec_char(Coded_Z),
 
326
    ?line [Coded_dollar] = cdrlib:enc_char($$, []),
 
327
    ?line {$$, <<>>} = cdrlib:dec_char(Coded_dollar),
 
328
    ok.
 
329
 
 
330
%%-----------------------------------------------------------------
 
331
%% Test Case: octet test
 
332
%% Description: 
 
333
%%-----------------------------------------------------------------
 
334
octet(doc) -> ["Description", "more description"];
 
335
octet(suite) -> [];
 
336
octet(_) ->
 
337
    ?line [Coded_ff] = cdrlib:enc_octet(16#ff, []),
 
338
    ?line {16#ff, <<>>} = cdrlib:dec_octet(Coded_ff),
 
339
    ?line [Coded_00] = cdrlib:enc_octet(16#00, []),
 
340
    ?line {16#00, <<>>} = cdrlib:dec_octet(Coded_00),
 
341
    ?line [Coded_5a] = cdrlib:enc_octet(16#5a, []),
 
342
    ?line {16#5a, <<>>} = cdrlib:dec_octet(Coded_5a),
 
343
    ?line [Coded_48] = cdrlib:enc_octet(16#48, []),
 
344
    ?line {16#48, <<>>} = cdrlib:dec_octet(Coded_48),
 
345
    ok.
 
346
 
 
347
 
 
348
 
 
349
%%-----------------------------------------------------------------
 
350
%% Test Case: float test
 
351
%% Description: 
 
352
%%-----------------------------------------------------------------
 
353
float(doc) -> ["Description", "more description"];
 
354
float(suite) -> [];
 
355
float(_) ->
 
356
    G = 16#7fffff / 16#800000 + 1.0,
 
357
    H1 = math:pow(2, 127),
 
358
    H2 = math:pow(2, -126),
 
359
    float_big_loop([-H1 * G, -H1 * 1.0, -H2 * G, -H2 * 1.0,
 
360
                    -4040.313131, -3.141592, 0.0, 3.141592, 4040.313131,
 
361
                    H1 * G, H1 * 1.0, H2 * G, H2 * 1.0]),
 
362
    float_little_loop([-H1 * G, -H1 * 1.0, -H2 * G, -H2 * 1.0,
 
363
                       -4040.313131, -3.141592, 0.0, 3.141592, 4040.313131,
 
364
                       H1 * G, H1 * 1.0, H2 * G, H2 * 1.0]),
 
365
    ok.
 
366
 
 
367
float_big_loop([]) ->
 
368
    ok;
 
369
float_big_loop([X |List]) ->
 
370
    ?line [CodedType] = cdrlib:enc_float(X, []),
 
371
    ?line {Y, <<>>} = cdrlib:dec_float(big, CodedType),
 
372
    ?line float_comp(X,Y),
 
373
    float_big_loop(List),
 
374
    ok.
 
375
 
 
376
float_little_loop([]) ->
 
377
    ok;
 
378
float_little_loop([X |List]) ->
 
379
    ?line [CodedType] = enc_float_little(X, []),
 
380
    ?line {Y, <<>>} = cdrlib:dec_float(little, CodedType),
 
381
    ?line float_comp(X,Y),
 
382
    float_little_loop(List),
 
383
    ok.
 
384
 
 
385
float_comp(X,Y) when X == 0.0, Y == 0.0 ->
 
386
    ok;
 
387
float_comp(X,Y) ->
 
388
    Div = abs(Y) / abs(X),
 
389
    %% io:format("~p~n", [float_to_list(Div)]),
 
390
    ?line true = (Div < 1.0000001),
 
391
    ?line true = (Div > 0.9999999),
 
392
    ok.
 
393
 
 
394
enc_float_little(X, Message) -> 
 
395
    [ <<X:32/little-float>> | Message].
 
396
 
 
397
%%-----------------------------------------------------------------
 
398
%% Test Case: double test
 
399
%% Description: 
 
400
%%-----------------------------------------------------------------
 
401
double(doc) -> ["Description", "more description"];
 
402
double(suite) -> [];
 
403
double(_) ->
 
404
    F = 16#0fffffffffffff / 16#10000000000000 + 1.0,
 
405
    E1 = math:pow(2, 1023),
 
406
    E2 = math:pow(2, -1022),
 
407
    G = 16#7fffff / 16#800000 + 1.0,
 
408
    H1 = math:pow(2, 128),
 
409
    H2 = math:pow(2, -127),
 
410
    double_big_loop([-E1 * F, -E1 * 1.0, -E2 * F, -E2 * 1.0,
 
411
                     -H1 * G, -H1 * 1.0, -H2 * G, -H2 * 1.0,
 
412
                     -4040.313131, -3.141592, 0.0, 3.141592, 4040.313131,
 
413
                     H1 * G, H1 * 1.0, H2 * G, H2 * 1.0,
 
414
                     E1 * F, E1 * 1.0, E2 * F, E2 * 1.0]),
 
415
    double_little_loop([-E1 * F, -E1 * 1.0, -E2 * F, -E2 * 1.0,
 
416
                        -H1 * G, -H1 * 1.0, -H2 * G, -H2 * 1.0,
 
417
                        -4040.313131, -3.141592, 0.0, 3.141592, 4040.313131,
 
418
                        H1 * G, H1 * 1.0, H2 * G, H2 * 1.0,
 
419
                        E1 * F, E1 * 1.0, E2 * F, E2 * 1.0]),
 
420
    ok.
 
421
 
 
422
double_big_loop([]) ->
 
423
    ok;
 
424
double_big_loop([X |List]) ->
 
425
    ?line [CodedType] = cdrlib:enc_double(X, []),
 
426
    ?line {Y, <<>>} = cdrlib:dec_double(big, CodedType),
 
427
    ?line double_comp(X,Y), 
 
428
    double_big_loop(List),
 
429
    ok.
 
430
 
 
431
double_little_loop([]) ->
 
432
    ok;
 
433
double_little_loop([X |List]) ->
 
434
    ?line [CodedType] = enc_double_little(X, []),
 
435
    ?line {Y, <<>>} = cdrlib:dec_double(little, CodedType),
 
436
    ?line double_comp(X,Y), 
 
437
    double_little_loop(List),
 
438
    ok.
 
439
 
 
440
enc_double_little(X, Message) -> 
 
441
    [ <<X:64/little-float>> | Message].
 
442
 
 
443
double_comp(X,Y) when X == 0.0, Y == 0.0 ->
 
444
    ok;
 
445
double_comp(X,Y) ->
 
446
    Div = abs(Y) / abs(X),
 
447
    %% io:format("~p~n", [float_to_list(Div)]),
 
448
    ?line true = (Div < 1.00000000000001),
 
449
    ?line true = (Div > 0.99999999999999),
 
450
    ok.
 
451
 
 
452
double_should_be_ok(doc) -> ["Description", "more description"];
 
453
double_should_be_ok(suite) -> [];
 
454
double_should_be_ok(_) ->
 
455
    F = 16#0fffffffffffff / 16#10000000000000 + 1.0,
 
456
    E1 = math:pow(2, 1024), % erlang can't handle this.
 
457
    E2 = math:pow(2, -1023),
 
458
    double_big_loop([-E1 * F, -E1 * 1.0, -E2 * F, -E2 * 1.0,
 
459
                     E1 * F, E1 * 1.0, E2 * F, E2 * 1.0]),
 
460
    double_little_loop([-E1 * F, -E1 * 1.0, -E2 * F, -E2 * 1.0,
 
461
                        E1 * F, E1 * 1.0, E2 * F, E2 * 1.0]),
 
462
    ok.
 
463
 
 
464
%%-----------------------------------------------------------------
 
465
%% Test Case: enum test
 
466
%% Description: 
 
467
%%-----------------------------------------------------------------
 
468
enum(doc) -> ["Description", "more description"];
 
469
enum(suite) -> [];
 
470
enum(_) ->
 
471
    enum_big(),
 
472
    enum_little(),
 
473
    ok.
 
474
 
 
475
enum_big() ->
 
476
    ?line [Coded_a] = cdrlib:enc_enum(a,[a,b,c],[]),
 
477
    ?line {a, <<>>} = cdrlib:dec_enum(big, ["a","b","c"], Coded_a),
 
478
    ?line [Coded_b] = cdrlib:enc_enum(b,[a,b,c],[]),
 
479
    ?line {b, <<>>} = cdrlib:dec_enum(big, ["a","b","c"], Coded_b),
 
480
    ?line [Coded_c] = cdrlib:enc_enum(c,[a,b,c],[]),
 
481
    ?line {c, <<>>} = cdrlib:dec_enum(big, ["a","b","c"], Coded_c),
 
482
    ok.
 
483
 
 
484
enum_little() ->
 
485
    ?line Coded_a = enc_r_enum(a,[a,b,c],[]),
 
486
    ?line {a, <<>>} = cdrlib:dec_enum(little, ["a","b","c"], Coded_a),
 
487
    ?line Coded_b = enc_r_enum(b,[a,b,c],[]),
 
488
    ?line {b, <<>>} = cdrlib:dec_enum(little, ["a","b","c"], Coded_b),
 
489
    ?line Coded_c = enc_r_enum(c,[a,b,c],[]),
 
490
    ?line {c, <<>>} = cdrlib:dec_enum(little, ["a","b","c"], Coded_c),
 
491
    ok.
 
492
 
 
493
enc_r_enum(Enum, ElemList, Message) ->
 
494
    Val = getEnumValue(ElemList,Enum, 0),
 
495
    enc_r_unsigned_long(Val, Message).
 
496
 
 
497
getEnumValue([Enum |_List], Enum, N) ->
 
498
    N;
 
499
getEnumValue([_ |List], Enum, N) ->
 
500
    getEnumValue(List, Enum, N + 1).
 
501
 
 
502
enc_r_unsigned_long(X, Message) -> 
 
503
    list_to_binary([(X) band 16#ff, ((X) bsr 8) band 16#ff,
 
504
                    ((X) bsr 16) band 16#ff, ((X) bsr 24) band 16#ff | Message]).