~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/diameter/src/base/diameter_types.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2010-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
-module(diameter_types).
 
21
 
 
22
%%
 
23
%% Encode/decode of RFC 3588 Data Formats, Basic (section 4.2) and
 
24
%% Derived (section 4.3).
 
25
%%
 
26
 
 
27
%% Basic types.
 
28
-export(['OctetString'/2,
 
29
         'Integer32'/2,
 
30
         'Integer64'/2,
 
31
         'Unsigned32'/2,
 
32
         'Unsigned64'/2,
 
33
         'Float32'/2,
 
34
         'Float64'/2]).
 
35
 
 
36
%% Derived types.
 
37
-export(['Address'/2,
 
38
         'Time'/2,
 
39
         'UTF8String'/2,
 
40
         'DiameterIdentity'/2,
 
41
         'DiameterURI'/2,
 
42
         'IPFilterRule'/2,
 
43
         'QoSFilterRule'/2]).
 
44
 
 
45
%% Functions taking the AVP name in question as second parameter.
 
46
-export(['OctetString'/3,
 
47
         'Integer32'/3,
 
48
         'Integer64'/3,
 
49
         'Unsigned32'/3,
 
50
         'Unsigned64'/3,
 
51
         'Float32'/3,
 
52
         'Float64'/3,
 
53
         'Address'/3,
 
54
         'Time'/3,
 
55
         'UTF8String'/3,
 
56
         'DiameterIdentity'/3,
 
57
         'DiameterURI'/3,
 
58
         'IPFilterRule'/3,
 
59
         'QoSFilterRule'/3]).
 
60
 
 
61
-include_lib("diameter/include/diameter.hrl").
 
62
 
 
63
-define(UINT(N,X), ((0 =< X) andalso (X < 1 bsl N))).
 
64
-define(SINT(N,X), ((-1*(1 bsl (N-1)) < X) andalso (X < 1 bsl (N-1)))).
 
65
 
 
66
%% The Grouped and Enumerated types are dealt with directly in
 
67
%% generated decode modules by way of diameter_gen.hrl and
 
68
%% diameter_codec.erl. Padding and the setting of Length and other
 
69
%% fields are also dealt with there.
 
70
 
 
71
%% 3588:
 
72
%%
 
73
%%   DIAMETER_INVALID_AVP_LENGTH        5014
 
74
%%      The request contained an AVP with an invalid length.  A Diameter
 
75
%%      message indicating this error MUST include the offending AVPs
 
76
%%      within a Failed-AVP AVP.
 
77
%%
 
78
-define(INVALID_LENGTH(Bin), erlang:error({'DIAMETER', 5014, Bin})).
 
79
 
 
80
%% -------------------------------------------------------------------------
 
81
%% 3588, 4.2.  Basic AVP Data Formats
 
82
%%
 
83
%%    The Data field is zero or more octets and contains information
 
84
%%    specific to the Attribute.  The format and length of the Data field
 
85
%%    is determined by the AVP Code and AVP Length fields.  The format of
 
86
%%    the Data field MUST be one of the following base data types or a data
 
87
%%    type derived from the base data types.  In the event that a new Basic
 
88
%%    AVP Data Format is needed, a new version of this RFC must be created.
 
89
%% --------------------
 
90
 
 
91
'OctetString'(decode, Bin)
 
92
  when is_binary(Bin) ->
 
93
    binary_to_list(Bin);
 
94
 
 
95
'OctetString'(encode = M, zero) ->
 
96
    'OctetString'(M, []);
 
97
 
 
98
'OctetString'(encode, Str) ->
 
99
    iolist_to_binary(Str).
 
100
 
 
101
%% --------------------
 
102
 
 
103
'Integer32'(decode, <<X:32/signed>>) ->
 
104
    X;
 
105
 
 
106
'Integer32'(decode, B) ->
 
107
    ?INVALID_LENGTH(B);
 
108
 
 
109
'Integer32'(encode = M, zero) ->
 
110
    'Integer32'(M, 0);
 
111
 
 
112
'Integer32'(encode, I)
 
113
  when ?SINT(32,I) ->
 
114
    <<I:32/signed>>.
 
115
 
 
116
%% --------------------
 
117
 
 
118
'Integer64'(decode, <<X:64/signed>>) ->
 
119
    X;
 
120
 
 
121
'Integer64'(decode, B) ->
 
122
    ?INVALID_LENGTH(B);
 
123
 
 
124
'Integer64'(encode = M, zero) ->
 
125
    'Integer64'(M, 0);
 
126
 
 
127
'Integer64'(encode, I)
 
128
  when ?SINT(64,I) ->
 
129
    <<I:64/signed>>.
 
130
 
 
131
%% --------------------
 
132
 
 
133
'Unsigned32'(decode, <<X:32>>) ->
 
134
    X;
 
135
 
 
136
'Unsigned32'(decode, B) ->
 
137
    ?INVALID_LENGTH(B);
 
138
 
 
139
'Unsigned32'(encode = M, zero) ->
 
140
    'Unsigned32'(M, 0);
 
141
 
 
142
'Unsigned32'(encode, I)
 
143
  when ?UINT(32,I) ->
 
144
    <<I:32>>.
 
145
 
 
146
%% --------------------
 
147
 
 
148
'Unsigned64'(decode, <<X:64>>) ->
 
149
    X;
 
150
 
 
151
'Unsigned64'(decode, B) ->
 
152
    ?INVALID_LENGTH(B);
 
153
 
 
154
'Unsigned64'(encode = M, zero) ->
 
155
    'Unsigned64'(M, 0);
 
156
 
 
157
'Unsigned64'(encode, I)
 
158
  when ?UINT(64,I) ->
 
159
    <<I:64>>.
 
160
 
 
161
%% --------------------
 
162
 
 
163
%% Decent summaries of the IEEE floating point formats can be
 
164
%% found at http://en.wikipedia.org/wiki/IEEE_754-1985 and
 
165
%% http://www.psc.edu/general/software/packages/ieee/ieee.php.
 
166
%%
 
167
%% That the bit syntax uses these formats isn't well documented but
 
168
%% this does indeed appear to be the case. However, the bit syntax
 
169
%% only encodes numeric values, not the standard's (signed) infinity
 
170
%% or NaN. It also encodes any large value as 'infinity', never 'NaN'.
 
171
%% Treat these equivalently on decode for this reason.
 
172
%%
 
173
%% An alternative would be to decode infinity/NaN to the largest
 
174
%% possible float but could likely lead to misleading results if
 
175
%% arithmetic is performed on the decoded value. Better to be explicit
 
176
%% that precision has been lost.
 
177
 
 
178
'Float32'(decode, <<S:1, 255:8, _:23>>) ->
 
179
    choose(S, infinity, '-infinity');
 
180
 
 
181
'Float32'(decode, <<X:32/float>>) ->
 
182
    X;
 
183
 
 
184
'Float32'(decode, B) ->
 
185
    ?INVALID_LENGTH(B);
 
186
 
 
187
'Float32'(encode = M, zero) ->
 
188
    'Float32'(M, 0.0);
 
189
 
 
190
'Float32'(encode, infinity) ->
 
191
    <<0:1, 255:8, 0:23>>;
 
192
 
 
193
'Float32'(encode, '-infinity') ->
 
194
    <<1:1, 255:8, 0:23>>;
 
195
 
 
196
'Float32'(encode, X)
 
197
  when is_float(X) ->
 
198
    <<X:32/float>>.
 
199
%% Note that this could also encode infinity/-infinity for large
 
200
%% (signed) numeric values. Note also that precision is lost just in
 
201
%% using the floating point syntax. For example:
 
202
%%
 
203
%% 1> B = <<3.14159:32/float>>.
 
204
%% <<64,73,15,208>>
 
205
%% 2> <<F:32/float>> = B.
 
206
%% <<64,73,15,208>>
 
207
%% 3> F.
 
208
%% 3.141590118408203
 
209
%%
 
210
%% (The 64 bit type does better.)
 
211
 
 
212
%% --------------------
 
213
 
 
214
%% The 64 bit format is entirely analogous to the 32 bit format.
 
215
 
 
216
'Float64'(decode, <<S:1, 2047:11, _:52>>) ->
 
217
    choose(S, infinity, '-infinity');
 
218
 
 
219
'Float64'(decode, <<X:64/float>>) ->
 
220
    X;
 
221
 
 
222
'Float64'(decode, B) ->
 
223
    ?INVALID_LENGTH(B);
 
224
 
 
225
'Float64'(encode, infinity) ->
 
226
    <<0:1, 2047:11, 0:52>>;
 
227
 
 
228
'Float64'(encode, '-infinity') ->
 
229
    <<1:1, 2047:11, 0:52>>;
 
230
 
 
231
'Float64'(encode = M, zero) ->
 
232
    'Float64'(M, 0.0);
 
233
 
 
234
'Float64'(encode, X)
 
235
  when is_float(X) ->
 
236
    <<X:64/float>>.
 
237
 
 
238
%% -------------------------------------------------------------------------
 
239
%% 3588, 4.3.  Derived AVP Data Formats
 
240
%%
 
241
%%    In addition to using the Basic AVP Data Formats, applications may
 
242
%%    define data formats derived from the Basic AVP Data Formats.  An
 
243
%%    application that defines new AVP Derived Data Formats MUST include
 
244
%%    them in a section entitled "AVP Derived Data Formats", using the same
 
245
%%    format as the definitions below.  Each new definition must be either
 
246
%%    defined or listed with a reference to the RFC that defines the
 
247
%%    format.
 
248
%% --------------------
 
249
 
 
250
'Address'(encode, zero) ->
 
251
    <<0:48>>;
 
252
 
 
253
'Address'(decode, <<1:16, B/binary>>)
 
254
  when size(B) == 4 ->
 
255
    list_to_tuple(binary_to_list(B));
 
256
 
 
257
'Address'(decode, <<2:16, B/binary>>)
 
258
  when size(B) == 16 ->
 
259
    list_to_tuple(v6dec(B, []));
 
260
 
 
261
'Address'(decode, <<A:16, _/binary>> = B)
 
262
  when 1 == A;
 
263
       2 == A ->
 
264
    ?INVALID_LENGTH(B);
 
265
 
 
266
'Address'(encode, T) ->
 
267
    ipenc(diameter_lib:ipaddr(T)).
 
268
 
 
269
ipenc(T)
 
270
  when is_tuple(T), size(T) == 4 ->
 
271
    B = list_to_binary(tuple_to_list(T)),
 
272
    <<1:16, B/binary>>;
 
273
 
 
274
ipenc(T)
 
275
  when is_tuple(T), size(T) == 8 ->
 
276
    B = v6enc(lists:reverse(tuple_to_list(T)), <<>>),
 
277
    <<2:16, B/binary>>.
 
278
 
 
279
v6dec(<<N:16, B/binary>>, Acc) ->
 
280
    v6dec(B, [N | Acc]);
 
281
 
 
282
v6dec(<<>>, Acc) ->
 
283
    lists:reverse(Acc).
 
284
 
 
285
v6enc([N | Rest], B)
 
286
  when ?UINT(16,N) ->
 
287
    v6enc(Rest, <<N:16, B/binary>>);
 
288
 
 
289
v6enc([], B) ->
 
290
    B.
 
291
 
 
292
%% --------------------
 
293
 
 
294
%% A DiameterIdentity is a FQDN as definined in RFC 1035, which is at
 
295
%% least one character.
 
296
 
 
297
'DiameterIdentity'(encode = M, zero) ->
 
298
    'OctetString'(M, [0]);
 
299
 
 
300
'DiameterIdentity'(encode = M, X) ->
 
301
    <<_,_/binary>> = 'OctetString'(M, X);
 
302
 
 
303
'DiameterIdentity'(decode = M, <<_,_/binary>> = X) ->
 
304
    'OctetString'(M, X).
 
305
 
 
306
%% --------------------
 
307
 
 
308
'DiameterURI'(decode, Bin)
 
309
  when is_binary(Bin) ->
 
310
    scan_uri(Bin);
 
311
 
 
312
%% The minimal DiameterURI is "aaa://x", 7 characters.
 
313
'DiameterURI'(encode = M, zero) ->
 
314
    'OctetString'(M, lists:duplicate(0,7));
 
315
 
 
316
'DiameterURI'(encode, #diameter_uri{type = Type,
 
317
                                    fqdn = D,
 
318
                                    port = P,
 
319
                                    transport = T,
 
320
                                    protocol = Prot}
 
321
                      = U) ->
 
322
    S = lists:append([atom_to_list(Type), "://", D,
 
323
                      ":", integer_to_list(P),
 
324
                      ";transport=", atom_to_list(T),
 
325
                      ";protocol=", atom_to_list(Prot)]),
 
326
    U = scan_uri(S), %% assert
 
327
    list_to_binary(S);
 
328
 
 
329
'DiameterURI'(encode, Str) ->
 
330
    Bin = iolist_to_binary(Str),
 
331
    #diameter_uri{} = scan_uri(Bin),  %% type check
 
332
    Bin.
 
333
 
 
334
%% --------------------
 
335
 
 
336
%% This minimal rule is "deny in 0 from 0.0.0.0 to 0.0.0.0", 33 characters.
 
337
'IPFilterRule'(encode = M, zero) ->
 
338
    'OctetString'(M, lists:duplicate(0,33));
 
339
 
 
340
%% TODO: parse grammar.
 
341
'IPFilterRule'(M, X) ->
 
342
    'OctetString'(M, X).
 
343
 
 
344
%% --------------------
 
345
 
 
346
%% This minimal rule is the same as for an IPFilterRule.
 
347
'QoSFilterRule'(encode = M, zero = X) ->
 
348
    'IPFilterRule'(M, X);
 
349
 
 
350
%% TODO: parse grammar.
 
351
'QoSFilterRule'(M, X) ->
 
352
    'OctetString'(M, X).
 
353
 
 
354
%% --------------------
 
355
 
 
356
'UTF8String'(decode, Bin) ->
 
357
    udec(Bin, []);
 
358
 
 
359
'UTF8String'(encode = M, zero) ->
 
360
    'UTF8String'(M, []);
 
361
 
 
362
'UTF8String'(encode, S) ->
 
363
    uenc(S, []).
 
364
 
 
365
udec(<<>>, Acc) ->
 
366
    lists:reverse(Acc);
 
367
 
 
368
udec(<<C/utf8, Rest/binary>>, Acc) ->
 
369
    udec(Rest, [C | Acc]).
 
370
 
 
371
uenc(E, Acc)
 
372
  when E == [];
 
373
       E == <<>> ->
 
374
    list_to_binary(lists:reverse(Acc));
 
375
 
 
376
uenc(<<C/utf8, Rest/binary>>, Acc) ->
 
377
    uenc(Rest, [<<C/utf8>> | Acc]);
 
378
 
 
379
uenc([[] | Rest], Acc) ->
 
380
    uenc(Rest, Acc);
 
381
 
 
382
uenc([[H|T] | Rest], Acc) ->
 
383
    uenc([H, T | Rest], Acc);
 
384
 
 
385
uenc([C | Rest], Acc) ->
 
386
    uenc(Rest, [<<C/utf8>> | Acc]).
 
387
 
 
388
%% --------------------
 
389
 
 
390
%% RFC 3588, 4.3:
 
391
%%
 
392
%%    Time
 
393
%%       The Time format is derived from the OctetString AVP Base Format.
 
394
%%       The string MUST contain four octets, in the same format as the
 
395
%%       first four bytes are in the NTP timestamp format.  The NTP
 
396
%%       Timestamp format is defined in chapter 3 of [SNTP].
 
397
%%
 
398
%%       This represents the number of seconds since 0h on 1 January 1900
 
399
%%       with respect to the Coordinated Universal Time (UTC).
 
400
%%
 
401
%%       On 6h 28m 16s UTC, 7 February 2036 the time value will overflow.
 
402
%%       SNTP [SNTP] describes a procedure to extend the time to 2104.
 
403
%%       This procedure MUST be supported by all DIAMETER nodes.
 
404
 
 
405
%% RFC 2030, 3:
 
406
%%
 
407
%%       As the NTP timestamp format has been in use for the last 17 years,
 
408
%%       it remains a possibility that it will be in use 40 years from now
 
409
%%       when the seconds field overflows. As it is probably inappropriate
 
410
%%       to archive NTP timestamps before bit 0 was set in 1968, a
 
411
%%       convenient way to extend the useful life of NTP timestamps is the
 
412
%%       following convention: If bit 0 is set, the UTC time is in the
 
413
%%       range 1968-2036 and UTC time is reckoned from 0h 0m 0s UTC on 1
 
414
%%       January 1900. If bit 0 is not set, the time is in the range 2036-
 
415
%%       2104 and UTC time is reckoned from 6h 28m 16s UTC on 7 February
 
416
%%       2036. Note that when calculating the correspondence, 2000 is not a
 
417
%%       leap year. Note also that leap seconds are not counted in the
 
418
%%       reckoning.
 
419
%%
 
420
%% The statement regarding year 2000 is wrong: errata id 518 at
 
421
%% http://www.rfc-editor.org/errata_search.php?rfc=2030 notes this.
 
422
 
 
423
-define(TIME_1900, 59958230400).  %% {{1900,1,1},{0,0,0}}
 
424
-define(TIME_2036, 64253197696).  %% {{2036,2,7},{6,28,16}}
 
425
%% TIME_2036 = TIME_1900 + (1 bsl 32)
 
426
 
 
427
%% Time maps [0, 1 bsl 31) onto [TIME_1900 + 1 bsl 31, TIME_2036 + 1 bsl 31)
 
428
%% by taking integers with the high-order bit set relative to TIME_1900
 
429
%% and those without relative to TIME_2036. This corresponds to the
 
430
%% following dates.
 
431
-define(TIME_MIN, {{1968,1,20},{3,14,8}}).  %% TIME_1900 + 1 bsl 31
 
432
-define(TIME_MAX, {{2104,2,26},{9,42,24}}). %% TIME_2036 + 1 bsl 31
 
433
 
 
434
'Time'(decode, <<Time:32>>) ->
 
435
    Offset = msb(1 == Time bsr 31),
 
436
    calendar:gregorian_seconds_to_datetime(Time + Offset);
 
437
 
 
438
'Time'(decode, B) ->
 
439
    ?INVALID_LENGTH(B);
 
440
 
 
441
'Time'(encode, {{_Y,_M,_D},{_HH,_MM,_SS}} = Datetime)
 
442
  when ?TIME_MIN =< Datetime, Datetime < ?TIME_MAX ->
 
443
    S = calendar:datetime_to_gregorian_seconds(Datetime),
 
444
    T = S - msb(S < ?TIME_2036),
 
445
    0 = T bsr 32,  %% sanity check
 
446
    <<T:32>>;
 
447
 
 
448
'Time'(encode, zero) ->
 
449
    <<0:32>>.
 
450
 
 
451
%% -------------------------------------------------------------------------
 
452
 
 
453
'OctetString'(M, _, Data) ->
 
454
    'OctetString'(M, Data).
 
455
 
 
456
'Integer32'(M, _, Data) ->
 
457
    'Integer32'(M, Data).
 
458
 
 
459
'Integer64'(M, _, Data) ->
 
460
    'Integer64'(M, Data).
 
461
 
 
462
'Unsigned32'(M, _, Data) ->
 
463
    'Unsigned32'(M, Data).
 
464
 
 
465
'Unsigned64'(M, _, Data) ->
 
466
    'Unsigned64'(M, Data).
 
467
 
 
468
'Float32'(M, _, Data) ->
 
469
    'Float32'(M, Data).
 
470
 
 
471
'Float64'(M, _, Data) ->
 
472
    'Float64'(M, Data).
 
473
 
 
474
'Address'(M, _, Data) ->
 
475
    'Address'(M, Data).
 
476
 
 
477
'Time'(M, _, Data) ->
 
478
    'Time'(M, Data).
 
479
 
 
480
'UTF8String'(M, _, Data) ->
 
481
    'UTF8String'(M, Data).
 
482
 
 
483
'DiameterIdentity'(M, _, Data) ->
 
484
    'DiameterIdentity'(M, Data).
 
485
 
 
486
'DiameterURI'(M, _, Data) ->
 
487
    'DiameterURI'(M, Data).
 
488
 
 
489
'IPFilterRule'(M, _, Data) ->
 
490
    'IPFilterRule'(M, Data).
 
491
 
 
492
'QoSFilterRule'(M, _, Data) ->
 
493
    'QoSFilterRule'(M, Data).
 
494
 
 
495
%% ===========================================================================
 
496
%% ===========================================================================
 
497
 
 
498
choose(0, X, _) -> X;
 
499
choose(1, _, X) -> X.
 
500
 
 
501
msb(true)  -> ?TIME_1900;
 
502
msb(false) -> ?TIME_2036.
 
503
 
 
504
%% RFC 3588, 4.3:
 
505
%%
 
506
%%       The DiameterURI MUST follow the Uniform Resource Identifiers (URI)
 
507
%%       syntax [URI] rules specified below:
 
508
%%
 
509
%%       "aaa://" FQDN [ port ] [ transport ] [ protocol ]
 
510
%%
 
511
%%                       ; No transport security
 
512
%%
 
513
%%       "aaas://" FQDN [ port ] [ transport ] [ protocol ]
 
514
%%
 
515
%%                       ; Transport security used
 
516
%%
 
517
%%       FQDN               = Fully Qualified Host Name
 
518
%%
 
519
%%       port               = ":" 1*DIGIT
 
520
%%
 
521
%%                       ; One of the ports used to listen for
 
522
%%                       ; incoming connections.
 
523
%%                       ; If absent,
 
524
%%                       ; the default Diameter port (3868) is
 
525
%%                       ; assumed.
 
526
%%
 
527
%%       transport          = ";transport=" transport-protocol
 
528
%%
 
529
%%                       ; One of the transports used to listen
 
530
%%                       ; for incoming connections.  If absent,
 
531
%%                       ; the default SCTP [SCTP] protocol is
 
532
%%                       ; assumed.  UDP MUST NOT be used when
 
533
%%                       ; the aaa-protocol field is set to
 
534
%%                       ; diameter.
 
535
%%
 
536
%%       transport-protocol = ( "tcp" / "sctp" / "udp" )
 
537
%%
 
538
%%       protocol           = ";protocol=" aaa-protocol
 
539
%%
 
540
%%                       ; If absent, the default AAA protocol
 
541
%%                       ; is diameter.
 
542
%%
 
543
%%       aaa-protocol       = ( "diameter" / "radius" / "tacacs+" )
 
544
 
 
545
scan_uri(Bin)
 
546
  when is_binary(Bin) ->
 
547
    scan_uri(binary_to_list(Bin));
 
548
scan_uri("aaa://" ++ Rest) ->
 
549
    scan_fqdn(Rest, #diameter_uri{type = aaa});
 
550
scan_uri("aaas://" ++ Rest) ->
 
551
    scan_fqdn(Rest, #diameter_uri{type = aaas}).
 
552
 
 
553
scan_fqdn(S, U) ->
 
554
    {[_|_] = F, Rest} = lists:splitwith(fun is_fqdn/1, S),
 
555
    scan_opt_port(Rest, U#diameter_uri{fqdn = F}).
 
556
 
 
557
scan_opt_port(":" ++ S, U) ->
 
558
    {[_|_] = P, Rest} = lists:splitwith(fun is_digit/1, S),
 
559
    scan_opt_transport(Rest, U#diameter_uri{port = list_to_integer(P)});
 
560
scan_opt_port(S, U) ->
 
561
    scan_opt_transport(S, U).
 
562
 
 
563
scan_opt_transport(";transport=" ++ S, U) ->
 
564
    {P, Rest} = transport(S),
 
565
    scan_opt_protocol(Rest, U#diameter_uri{transport = P});
 
566
scan_opt_transport(S, U) ->
 
567
    scan_opt_protocol(S, U).
 
568
 
 
569
scan_opt_protocol(";protocol=" ++ S, U) ->
 
570
    {P, ""} = protocol(S),
 
571
    U#diameter_uri{protocol = P};
 
572
scan_opt_protocol("", U) ->
 
573
    U.
 
574
 
 
575
transport("tcp" ++ S) ->
 
576
    {tcp, S};
 
577
transport("sctp" ++ S) ->
 
578
    {sctp, S};
 
579
transport("udp" ++ S) ->
 
580
    {udp, S}.
 
581
 
 
582
protocol("diameter" ++ S) ->
 
583
    {diameter, S};
 
584
protocol("radius" ++ S) ->
 
585
    {radius, S};
 
586
protocol("tacacs+" ++ S) ->
 
587
    {'tacacs+', S}.
 
588
 
 
589
is_fqdn(C) ->
 
590
    is_digit(C) orelse is_alpha(C) orelse C == $. orelse C == $-.
 
591
 
 
592
is_alpha(C) ->
 
593
    ($a =< C andalso C =< $z) orelse ($A =< C andalso C =< $Z).
 
594
 
 
595
is_digit(C) ->
 
596
    $0 =< C andalso C =< $9.